module Godot.Api.Auto where
import Data.Coerce
import Foreign.C
import Godot.Internal.Dispatch
import System.IO.Unsafe
import Godot.Gdnative.Internal
import Godot.Gdnative.Types

newtype GodotGlobalConstants = GodotGlobalConstants GodotObject
                                 deriving newtype AsVariant
bindObject_free
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "free" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_free #-}

instance Method "free" GodotObject (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_free (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject__notification
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "_notification" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject__notification #-}

instance Method "_notification" GodotObject (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject__notification (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject__set
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "_set" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject__set #-}

instance Method "_set" GodotObject
           (GodotString -> GodotVariant -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject__set (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject__get
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "_get" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject__get #-}

instance Method "_get" GodotObject (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject__get (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject__get_property_list
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "_get_property_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject__get_property_list #-}

instance Method "_get_property_list" GodotObject (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject__get_property_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject__init
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "_init" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject__init #-}

instance Method "_init" GodotObject (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject__init (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_class
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_class" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_class #-}

instance Method "get_class" GodotObject (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_class (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_is_class
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "is_class" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_is_class #-}

instance Method "is_class" GodotObject (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_is_class (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_set
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "set" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_set #-}

instance Method "set" GodotObject
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_set (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get #-}

instance Method "get" GodotObject (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_set_indexed
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "set_indexed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_set_indexed #-}

instance Method "set_indexed" GodotObject
           (GodotNodePath -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_set_indexed (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_indexed
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_indexed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_indexed #-}

instance Method "get_indexed" GodotObject
           (GodotNodePath -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_indexed (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_property_list
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_property_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_property_list #-}

instance Method "get_property_list" GodotObject (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_property_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_method_list
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_method_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_method_list #-}

instance Method "get_method_list" GodotObject (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_method_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_notification
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "notification" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_notification #-}

instance Method "notification" GodotObject (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_notification (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_instance_id
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_instance_id #-}

instance Method "get_instance_id" GodotObject (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_instance_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_set_script
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "set_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_set_script #-}

instance Method "set_script" GodotObject (GodotReference -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_set_script (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_script
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_script #-}

instance Method "get_script" GodotObject (IO GodotReference) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_script (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_set_meta
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "set_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_set_meta #-}

instance Method "set_meta" GodotObject
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_set_meta (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_meta
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_meta #-}

instance Method "get_meta" GodotObject
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_meta (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_has_meta
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "has_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_has_meta #-}

instance Method "has_meta" GodotObject (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_has_meta (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_meta_list
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_meta_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_meta_list #-}

instance Method "get_meta_list" GodotObject
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_meta_list (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_add_user_signal
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "add_user_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_add_user_signal #-}

instance Method "add_user_signal" GodotObject
           (GodotString -> GodotArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_add_user_signal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_has_user_signal
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "has_user_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_has_user_signal #-}

instance Method "has_user_signal" GodotObject
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_has_user_signal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_callv
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "callv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_callv #-}

instance Method "callv" GodotObject
           (GodotString -> GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_callv (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_has_method
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "has_method" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_has_method #-}

instance Method "has_method" GodotObject (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_has_method (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_signal_list
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_signal_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_signal_list #-}

instance Method "get_signal_list" GodotObject (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_signal_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_signal_connection_list
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_signal_connection_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_signal_connection_list #-}

instance Method "get_signal_connection_list" GodotObject
           (GodotString -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_signal_connection_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_get_incoming_connections
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "get_incoming_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_get_incoming_connections #-}

instance Method "get_incoming_connections" GodotObject
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_get_incoming_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_connect
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "connect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_connect #-}

instance Method "connect" GodotObject
           (GodotString ->
              GodotObject -> GodotString -> GodotArray -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_connect (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_disconnect
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "disconnect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_disconnect #-}

instance Method "disconnect" GodotObject
           (GodotString -> GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_disconnect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_is_connected
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "is_connected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_is_connected #-}

instance Method "is_connected" GodotObject
           (GodotString -> GodotObject -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_is_connected (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_set_block_signals
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "set_block_signals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_set_block_signals #-}

instance Method "set_block_signals" GodotObject (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_set_block_signals (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_is_blocking_signals
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "is_blocking_signals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_is_blocking_signals #-}

instance Method "is_blocking_signals" GodotObject (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_is_blocking_signals (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_property_list_changed_notify
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "property_list_changed_notify" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_property_list_changed_notify #-}

instance Method "property_list_changed_notify" GodotObject (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_property_list_changed_notify
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_set_message_translation
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "set_message_translation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_set_message_translation #-}

instance Method "set_message_translation" GodotObject
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_set_message_translation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_can_translate_messages
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "can_translate_messages" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_can_translate_messages #-}

instance Method "can_translate_messages" GodotObject (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_can_translate_messages
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_tr
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "tr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_tr #-}

instance Method "tr" GodotObject (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_tr (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindObject_is_queued_for_deletion
  = unsafePerformIO $
      withCString "Object" $
        \ clsNamePtr ->
          withCString "is_queued_for_deletion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindObject_is_queued_for_deletion #-}

instance Method "is_queued_for_deletion" GodotObject (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindObject_is_queued_for_deletion
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotReference = GodotReference GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotReference where
        type BaseClass GodotReference = GodotObject
        super = coerce
bindReference_init_ref
  = unsafePerformIO $
      withCString "Reference" $
        \ clsNamePtr ->
          withCString "init_ref" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReference_init_ref #-}

instance Method "init_ref" GodotReference (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReference_init_ref (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReference_reference
  = unsafePerformIO $
      withCString "Reference" $
        \ clsNamePtr ->
          withCString "reference" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReference_reference #-}

instance Method "reference" GodotReference (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReference_reference (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReference_unreference
  = unsafePerformIO $
      withCString "Reference" $
        \ clsNamePtr ->
          withCString "unreference" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReference_unreference #-}

instance Method "unreference" GodotReference (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReference_unreference (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotResource = GodotResource GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotResource where
        type BaseClass GodotResource = GodotReference
        super = coerce
bindResource__setup_local_to_scene
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "_setup_local_to_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource__setup_local_to_scene #-}

instance Method "_setup_local_to_scene" GodotResource (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource__setup_local_to_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_set_path
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "set_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_set_path #-}

instance Method "set_path" GodotResource (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_set_path (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_take_over_path
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "take_over_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_take_over_path #-}

instance Method "take_over_path" GodotResource
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_take_over_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_get_path
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "get_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_get_path #-}

instance Method "get_path" GodotResource (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_get_path (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_set_name
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "set_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_set_name #-}

instance Method "set_name" GodotResource (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_set_name (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_get_name
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_get_name #-}

instance Method "get_name" GodotResource (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_get_name (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_get_rid
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "get_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_get_rid #-}

instance Method "get_rid" GodotResource (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_get_rid (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_set_local_to_scene
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "set_local_to_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_set_local_to_scene #-}

instance Method "set_local_to_scene" GodotResource (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_set_local_to_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_is_local_to_scene
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "is_local_to_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_is_local_to_scene #-}

instance Method "is_local_to_scene" GodotResource (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_is_local_to_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_get_local_scene
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "get_local_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_get_local_scene #-}

instance Method "get_local_scene" GodotResource (IO GodotNode)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_get_local_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_setup_local_to_scene
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "setup_local_to_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_setup_local_to_scene #-}

instance Method "setup_local_to_scene" GodotResource (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_setup_local_to_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResource_duplicate
  = unsafePerformIO $
      withCString "Resource" $
        \ clsNamePtr ->
          withCString "duplicate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResource_duplicate #-}

instance Method "duplicate" GodotResource
           (Bool -> IO GodotResource)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResource_duplicate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotScript = GodotScript GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotScript where
        type BaseClass GodotScript = GodotResource
        super = coerce
bindScript_can_instance
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "can_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_can_instance #-}

instance Method "can_instance" GodotScript (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_can_instance (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_instance_has
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "instance_has" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_instance_has #-}

instance Method "instance_has" GodotScript (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_instance_has (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_has_source_code
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "has_source_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_has_source_code #-}

instance Method "has_source_code" GodotScript (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_has_source_code (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_get_source_code
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "get_source_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_get_source_code #-}

instance Method "get_source_code" GodotScript (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_get_source_code (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_set_source_code
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "set_source_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_set_source_code #-}

instance Method "set_source_code" GodotScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_set_source_code (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_reload
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "reload" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_reload #-}

instance Method "reload" GodotScript (Bool -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_reload (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_get_base_script
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "get_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_get_base_script #-}

instance Method "get_base_script" GodotScript (IO GodotScript)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_get_base_script (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_get_instance_base_type
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "get_instance_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_get_instance_base_type #-}

instance Method "get_instance_base_type" GodotScript
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_get_instance_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_has_script_signal
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "has_script_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_has_script_signal #-}

instance Method "has_script_signal" GodotScript
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_has_script_signal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScript_is_tool
  = unsafePerformIO $
      withCString "Script" $
        \ clsNamePtr ->
          withCString "is_tool" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScript_is_tool #-}

instance Method "is_tool" GodotScript (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScript_is_tool (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWeakRef = GodotWeakRef GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotWeakRef where
        type BaseClass GodotWeakRef = GodotReference
        super = coerce
bindWeakRef_get_ref
  = unsafePerformIO $
      withCString "WeakRef" $
        \ clsNamePtr ->
          withCString "get_ref" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWeakRef_get_ref #-}

instance Method "get_ref" GodotWeakRef (IO GodotVariant) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWeakRef_get_ref (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotImage = GodotImage GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotImage where
        type BaseClass GodotImage = GodotResource
        super = coerce
bindImage_get_width
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_width #-}

instance Method "get_width" GodotImage (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_width (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_height
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_height #-}

instance Method "get_height" GodotImage (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_height (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_size
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_size #-}

instance Method "get_size" GodotImage (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_size (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_has_mipmaps
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "has_mipmaps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_has_mipmaps #-}

instance Method "has_mipmaps" GodotImage (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_has_mipmaps (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_format
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_format #-}

instance Method "get_format" GodotImage (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_format (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_data
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_data #-}

instance Method "get_data" GodotImage (IO GodotPoolByteArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_convert
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "convert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_convert #-}

instance Method "convert" GodotImage (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_convert (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_mipmap_offset
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_mipmap_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_mipmap_offset #-}

instance Method "get_mipmap_offset" GodotImage (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_mipmap_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_resize_to_po2
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "resize_to_po2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_resize_to_po2 #-}

instance Method "resize_to_po2" GodotImage (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_resize_to_po2 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_resize
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "resize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_resize #-}

instance Method "resize" GodotImage (Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_resize (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_shrink_x2
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "shrink_x2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_shrink_x2 #-}

instance Method "shrink_x2" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_shrink_x2 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_expand_x2_hq2x
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "expand_x2_hq2x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_expand_x2_hq2x #-}

instance Method "expand_x2_hq2x" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_expand_x2_hq2x (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_crop
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "crop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_crop #-}

instance Method "crop" GodotImage (Int -> Int -> IO ()) where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_crop (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_flip_x
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "flip_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_flip_x #-}

instance Method "flip_x" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_flip_x (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_flip_y
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "flip_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_flip_y #-}

instance Method "flip_y" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_flip_y (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_generate_mipmaps
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "generate_mipmaps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_generate_mipmaps #-}

instance Method "generate_mipmaps" GodotImage (Bool -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_generate_mipmaps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_clear_mipmaps
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "clear_mipmaps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_clear_mipmaps #-}

instance Method "clear_mipmaps" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_clear_mipmaps (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_create
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_create #-}

instance Method "create" GodotImage
           (Int -> Int -> Bool -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_create (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_create_from_data
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "create_from_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_create_from_data #-}

instance Method "create_from_data" GodotImage
           (Int -> Int -> Bool -> Int -> GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_create_from_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_is_empty
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "is_empty" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_is_empty #-}

instance Method "is_empty" GodotImage (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_is_empty (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_load
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "load" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_load #-}

instance Method "load" GodotImage (GodotString -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_load (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_save_png
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "save_png" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_save_png #-}

instance Method "save_png" GodotImage (GodotString -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_save_png (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_detect_alpha
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "detect_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_detect_alpha #-}

instance Method "detect_alpha" GodotImage (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_detect_alpha (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_is_invisible
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "is_invisible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_is_invisible #-}

instance Method "is_invisible" GodotImage (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_is_invisible (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_compress
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "compress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_compress #-}

instance Method "compress" GodotImage
           (Int -> Int -> Float -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_compress (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_decompress
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "decompress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_decompress #-}

instance Method "decompress" GodotImage (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_decompress (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_is_compressed
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "is_compressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_is_compressed #-}

instance Method "is_compressed" GodotImage (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_is_compressed (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_fix_alpha_edges
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "fix_alpha_edges" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_fix_alpha_edges #-}

instance Method "fix_alpha_edges" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_fix_alpha_edges (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_premultiply_alpha
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "premultiply_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_premultiply_alpha #-}

instance Method "premultiply_alpha" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_premultiply_alpha (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_srgb_to_linear
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "srgb_to_linear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_srgb_to_linear #-}

instance Method "srgb_to_linear" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_srgb_to_linear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_normalmap_to_xy
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "normalmap_to_xy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_normalmap_to_xy #-}

instance Method "normalmap_to_xy" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_normalmap_to_xy (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_rgbe_to_srgb
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "rgbe_to_srgb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_rgbe_to_srgb #-}

instance Method "rgbe_to_srgb" GodotImage (IO GodotImage) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_rgbe_to_srgb (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_bumpmap_to_normalmap
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "bumpmap_to_normalmap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_bumpmap_to_normalmap #-}

instance Method "bumpmap_to_normalmap" GodotImage (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_bumpmap_to_normalmap (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_blit_rect
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "blit_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_blit_rect #-}

instance Method "blit_rect" GodotImage
           (GodotImage -> GodotRect2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_blit_rect (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_blit_rect_mask
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "blit_rect_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_blit_rect_mask #-}

instance Method "blit_rect_mask" GodotImage
           (GodotImage -> GodotImage -> GodotRect2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_blit_rect_mask (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_blend_rect
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "blend_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_blend_rect #-}

instance Method "blend_rect" GodotImage
           (GodotImage -> GodotRect2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_blend_rect (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_blend_rect_mask
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "blend_rect_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_blend_rect_mask #-}

instance Method "blend_rect_mask" GodotImage
           (GodotImage -> GodotImage -> GodotRect2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_blend_rect_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_fill
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "fill" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_fill #-}

instance Method "fill" GodotImage (GodotColor -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_fill (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_used_rect
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_used_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_used_rect #-}

instance Method "get_used_rect" GodotImage (IO GodotRect2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_used_rect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_rect
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_rect #-}

instance Method "get_rect" GodotImage (GodotRect2 -> IO GodotImage)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_rect (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_copy_from
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "copy_from" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_copy_from #-}

instance Method "copy_from" GodotImage (GodotImage -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_copy_from (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage__set_data
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage__set_data #-}

instance Method "_set_data" GodotImage (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage__set_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage__get_data
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage__get_data #-}

instance Method "_get_data" GodotImage (IO GodotDictionary) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage__get_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_lock
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_lock #-}

instance Method "lock" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_lock (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_unlock
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "unlock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_unlock #-}

instance Method "unlock" GodotImage (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_unlock (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_pixelv
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_pixelv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_pixelv #-}

instance Method "get_pixelv" GodotImage
           (GodotVector2 -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_pixelv (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_get_pixel
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "get_pixel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_get_pixel #-}

instance Method "get_pixel" GodotImage
           (Int -> Int -> IO GodotColor)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_get_pixel (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_set_pixelv
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "set_pixelv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_set_pixelv #-}

instance Method "set_pixelv" GodotImage
           (GodotVector2 -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_set_pixelv (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_set_pixel
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "set_pixel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_set_pixel #-}

instance Method "set_pixel" GodotImage
           (Int -> Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_set_pixel (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_load_png_from_buffer
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "load_png_from_buffer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_load_png_from_buffer #-}

instance Method "load_png_from_buffer" GodotImage
           (GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_load_png_from_buffer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_load_jpg_from_buffer
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "load_jpg_from_buffer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_load_jpg_from_buffer #-}

instance Method "load_jpg_from_buffer" GodotImage
           (GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_load_jpg_from_buffer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImage_load_webp_from_buffer
  = unsafePerformIO $
      withCString "Image" $
        \ clsNamePtr ->
          withCString "load_webp_from_buffer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImage_load_webp_from_buffer #-}

instance Method "load_webp_from_buffer" GodotImage
           (GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImage_load_webp_from_buffer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEvent = GodotInputEvent GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotInputEvent where
        type BaseClass GodotInputEvent = GodotResource
        super = coerce
bindInputEvent_set_device
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "set_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_set_device #-}

instance Method "set_device" GodotInputEvent (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_set_device (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_get_device
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "get_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_get_device #-}

instance Method "get_device" GodotInputEvent (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_get_device (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_is_action
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "is_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_is_action #-}

instance Method "is_action" GodotInputEvent
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_is_action (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_is_action_pressed
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "is_action_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_is_action_pressed #-}

instance Method "is_action_pressed" GodotInputEvent
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_is_action_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_is_action_released
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "is_action_released" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_is_action_released #-}

instance Method "is_action_released" GodotInputEvent
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_is_action_released
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_get_action_strength
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "get_action_strength" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_get_action_strength #-}

instance Method "get_action_strength" GodotInputEvent
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_get_action_strength
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_is_pressed
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_is_pressed #-}

instance Method "is_pressed" GodotInputEvent (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_is_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_is_echo
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "is_echo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_is_echo #-}

instance Method "is_echo" GodotInputEvent (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_is_echo (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_as_text
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "as_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_as_text #-}

instance Method "as_text" GodotInputEvent (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_as_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_shortcut_match
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "shortcut_match" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_shortcut_match #-}

instance Method "shortcut_match" GodotInputEvent
           (GodotInputEvent -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_shortcut_match (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_is_action_type
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "is_action_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_is_action_type #-}

instance Method "is_action_type" GodotInputEvent (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_is_action_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEvent_xformed_by
  = unsafePerformIO $
      withCString "InputEvent" $
        \ clsNamePtr ->
          withCString "xformed_by" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEvent_xformed_by #-}

instance Method "xformed_by" GodotInputEvent
           (GodotTransform2d -> GodotVector2 -> IO GodotInputEvent)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEvent_xformed_by (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventWithModifiers = GodotInputEventWithModifiers GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotInputEventWithModifiers where
        type BaseClass GodotInputEventWithModifiers = GodotInputEvent
        super = coerce
bindInputEventWithModifiers_set_alt
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "set_alt" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_set_alt #-}

instance Method "set_alt" GodotInputEventWithModifiers
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_set_alt
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_get_alt
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "get_alt" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_get_alt #-}

instance Method "get_alt" GodotInputEventWithModifiers (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_get_alt
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_set_shift
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "set_shift" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_set_shift #-}

instance Method "set_shift" GodotInputEventWithModifiers
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_set_shift
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_get_shift
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "get_shift" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_get_shift #-}

instance Method "get_shift" GodotInputEventWithModifiers (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_get_shift
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_set_control
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "set_control" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_set_control #-}

instance Method "set_control" GodotInputEventWithModifiers
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_set_control
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_get_control
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "get_control" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_get_control #-}

instance Method "get_control" GodotInputEventWithModifiers
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_get_control
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_set_metakey
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "set_metakey" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_set_metakey #-}

instance Method "set_metakey" GodotInputEventWithModifiers
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_set_metakey
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_get_metakey
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "get_metakey" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_get_metakey #-}

instance Method "get_metakey" GodotInputEventWithModifiers
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_get_metakey
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_set_command
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "set_command" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_set_command #-}

instance Method "set_command" GodotInputEventWithModifiers
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_set_command
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventWithModifiers_get_command
  = unsafePerformIO $
      withCString "InputEventWithModifiers" $
        \ clsNamePtr ->
          withCString "get_command" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventWithModifiers_get_command #-}

instance Method "get_command" GodotInputEventWithModifiers
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventWithModifiers_get_command
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventKey = GodotInputEventKey GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotInputEventKey where
        type BaseClass GodotInputEventKey = GodotInputEventWithModifiers
        super = coerce
bindInputEventKey_is_pressed
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_is_pressed #-}

instance Method "is_pressed" GodotInputEventKey (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_is_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_is_echo
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "is_echo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_is_echo #-}

instance Method "is_echo" GodotInputEventKey (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_is_echo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_set_pressed
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "set_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_set_pressed #-}

instance Method "set_pressed" GodotInputEventKey (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_set_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_set_scancode
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "set_scancode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_set_scancode #-}

instance Method "set_scancode" GodotInputEventKey (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_set_scancode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_get_scancode
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "get_scancode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_get_scancode #-}

instance Method "get_scancode" GodotInputEventKey (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_get_scancode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_set_unicode
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "set_unicode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_set_unicode #-}

instance Method "set_unicode" GodotInputEventKey (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_set_unicode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_get_unicode
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "get_unicode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_get_unicode #-}

instance Method "get_unicode" GodotInputEventKey (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_get_unicode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_set_echo
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "set_echo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_set_echo #-}

instance Method "set_echo" GodotInputEventKey (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventKey_set_echo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventKey_get_scancode_with_modifiers
  = unsafePerformIO $
      withCString "InputEventKey" $
        \ clsNamePtr ->
          withCString "get_scancode_with_modifiers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventKey_get_scancode_with_modifiers #-}

instance Method "get_scancode_with_modifiers" GodotInputEventKey
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindInputEventKey_get_scancode_with_modifiers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventMouse = GodotInputEventMouse GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotInputEventMouse where
        type BaseClass GodotInputEventMouse = GodotInputEventWithModifiers
        super = coerce
bindInputEventMouse_set_button_mask
  = unsafePerformIO $
      withCString "InputEventMouse" $
        \ clsNamePtr ->
          withCString "set_button_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouse_set_button_mask #-}

instance Method "set_button_mask" GodotInputEventMouse
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouse_set_button_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouse_get_button_mask
  = unsafePerformIO $
      withCString "InputEventMouse" $
        \ clsNamePtr ->
          withCString "get_button_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouse_get_button_mask #-}

instance Method "get_button_mask" GodotInputEventMouse (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouse_get_button_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouse_set_position
  = unsafePerformIO $
      withCString "InputEventMouse" $
        \ clsNamePtr ->
          withCString "set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouse_set_position #-}

instance Method "set_position" GodotInputEventMouse
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouse_set_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouse_get_position
  = unsafePerformIO $
      withCString "InputEventMouse" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouse_get_position #-}

instance Method "get_position" GodotInputEventMouse
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouse_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouse_set_global_position
  = unsafePerformIO $
      withCString "InputEventMouse" $
        \ clsNamePtr ->
          withCString "set_global_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouse_set_global_position #-}

instance Method "set_global_position" GodotInputEventMouse
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouse_set_global_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouse_get_global_position
  = unsafePerformIO $
      withCString "InputEventMouse" $
        \ clsNamePtr ->
          withCString "get_global_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouse_get_global_position #-}

instance Method "get_global_position" GodotInputEventMouse
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouse_get_global_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventMouseButton = GodotInputEventMouseButton GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotInputEventMouseButton where
        type BaseClass GodotInputEventMouseButton = GodotInputEventMouse
        super = coerce
bindInputEventMouseButton_is_pressed
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_is_pressed #-}

instance Method "is_pressed" GodotInputEventMouseButton (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_is_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseButton_set_factor
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "set_factor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_set_factor #-}

instance Method "set_factor" GodotInputEventMouseButton
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_set_factor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseButton_get_factor
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "get_factor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_get_factor #-}

instance Method "get_factor" GodotInputEventMouseButton (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_get_factor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseButton_set_button_index
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "set_button_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_set_button_index #-}

instance Method "set_button_index" GodotInputEventMouseButton
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_set_button_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseButton_get_button_index
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "get_button_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_get_button_index #-}

instance Method "get_button_index" GodotInputEventMouseButton
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_get_button_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseButton_set_pressed
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "set_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_set_pressed #-}

instance Method "set_pressed" GodotInputEventMouseButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_set_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseButton_set_doubleclick
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "set_doubleclick" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_set_doubleclick #-}

instance Method "set_doubleclick" GodotInputEventMouseButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_set_doubleclick
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseButton_is_doubleclick
  = unsafePerformIO $
      withCString "InputEventMouseButton" $
        \ clsNamePtr ->
          withCString "is_doubleclick" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseButton_is_doubleclick #-}

instance Method "is_doubleclick" GodotInputEventMouseButton
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseButton_is_doubleclick
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventMouseMotion = GodotInputEventMouseMotion GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotInputEventMouseMotion where
        type BaseClass GodotInputEventMouseMotion = GodotInputEventMouse
        super = coerce
bindInputEventMouseMotion_set_relative
  = unsafePerformIO $
      withCString "InputEventMouseMotion" $
        \ clsNamePtr ->
          withCString "set_relative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseMotion_set_relative #-}

instance Method "set_relative" GodotInputEventMouseMotion
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseMotion_set_relative
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseMotion_get_relative
  = unsafePerformIO $
      withCString "InputEventMouseMotion" $
        \ clsNamePtr ->
          withCString "get_relative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseMotion_get_relative #-}

instance Method "get_relative" GodotInputEventMouseMotion
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseMotion_get_relative
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseMotion_set_speed
  = unsafePerformIO $
      withCString "InputEventMouseMotion" $
        \ clsNamePtr ->
          withCString "set_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseMotion_set_speed #-}

instance Method "set_speed" GodotInputEventMouseMotion
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseMotion_set_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMouseMotion_get_speed
  = unsafePerformIO $
      withCString "InputEventMouseMotion" $
        \ clsNamePtr ->
          withCString "get_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMouseMotion_get_speed #-}

instance Method "get_speed" GodotInputEventMouseMotion
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMouseMotion_get_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventJoypadButton = GodotInputEventJoypadButton GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotInputEventJoypadButton where
        type BaseClass GodotInputEventJoypadButton = GodotInputEvent
        super = coerce
bindInputEventJoypadButton_is_pressed
  = unsafePerformIO $
      withCString "InputEventJoypadButton" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadButton_is_pressed #-}

instance Method "is_pressed" GodotInputEventJoypadButton (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadButton_is_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadButton_set_button_index
  = unsafePerformIO $
      withCString "InputEventJoypadButton" $
        \ clsNamePtr ->
          withCString "set_button_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadButton_set_button_index #-}

instance Method "set_button_index" GodotInputEventJoypadButton
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadButton_set_button_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadButton_get_button_index
  = unsafePerformIO $
      withCString "InputEventJoypadButton" $
        \ clsNamePtr ->
          withCString "get_button_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadButton_get_button_index #-}

instance Method "get_button_index" GodotInputEventJoypadButton
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadButton_get_button_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadButton_set_pressure
  = unsafePerformIO $
      withCString "InputEventJoypadButton" $
        \ clsNamePtr ->
          withCString "set_pressure" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadButton_set_pressure #-}

instance Method "set_pressure" GodotInputEventJoypadButton
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadButton_set_pressure
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadButton_get_pressure
  = unsafePerformIO $
      withCString "InputEventJoypadButton" $
        \ clsNamePtr ->
          withCString "get_pressure" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadButton_get_pressure #-}

instance Method "get_pressure" GodotInputEventJoypadButton
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadButton_get_pressure
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadButton_set_pressed
  = unsafePerformIO $
      withCString "InputEventJoypadButton" $
        \ clsNamePtr ->
          withCString "set_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadButton_set_pressed #-}

instance Method "set_pressed" GodotInputEventJoypadButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadButton_set_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventJoypadMotion = GodotInputEventJoypadMotion GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotInputEventJoypadMotion where
        type BaseClass GodotInputEventJoypadMotion = GodotInputEvent
        super = coerce
bindInputEventJoypadMotion_set_axis
  = unsafePerformIO $
      withCString "InputEventJoypadMotion" $
        \ clsNamePtr ->
          withCString "set_axis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadMotion_set_axis #-}

instance Method "set_axis" GodotInputEventJoypadMotion
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadMotion_set_axis
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadMotion_get_axis
  = unsafePerformIO $
      withCString "InputEventJoypadMotion" $
        \ clsNamePtr ->
          withCString "get_axis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadMotion_get_axis #-}

instance Method "get_axis" GodotInputEventJoypadMotion (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadMotion_get_axis
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadMotion_set_axis_value
  = unsafePerformIO $
      withCString "InputEventJoypadMotion" $
        \ clsNamePtr ->
          withCString "set_axis_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadMotion_set_axis_value #-}

instance Method "set_axis_value" GodotInputEventJoypadMotion
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadMotion_set_axis_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventJoypadMotion_get_axis_value
  = unsafePerformIO $
      withCString "InputEventJoypadMotion" $
        \ clsNamePtr ->
          withCString "get_axis_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventJoypadMotion_get_axis_value #-}

instance Method "get_axis_value" GodotInputEventJoypadMotion
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventJoypadMotion_get_axis_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventScreenDrag = GodotInputEventScreenDrag GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotInputEventScreenDrag where
        type BaseClass GodotInputEventScreenDrag = GodotInputEvent
        super = coerce
bindInputEventScreenDrag_set_index
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "set_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_set_index #-}

instance Method "set_index" GodotInputEventScreenDrag
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_set_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenDrag_get_index
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "get_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_get_index #-}

instance Method "get_index" GodotInputEventScreenDrag (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_get_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenDrag_set_position
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_set_position #-}

instance Method "set_position" GodotInputEventScreenDrag
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_set_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenDrag_get_position
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_get_position #-}

instance Method "get_position" GodotInputEventScreenDrag
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenDrag_set_relative
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "set_relative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_set_relative #-}

instance Method "set_relative" GodotInputEventScreenDrag
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_set_relative
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenDrag_get_relative
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "get_relative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_get_relative #-}

instance Method "get_relative" GodotInputEventScreenDrag
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_get_relative
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenDrag_set_speed
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "set_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_set_speed #-}

instance Method "set_speed" GodotInputEventScreenDrag
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_set_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenDrag_get_speed
  = unsafePerformIO $
      withCString "InputEventScreenDrag" $
        \ clsNamePtr ->
          withCString "get_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenDrag_get_speed #-}

instance Method "get_speed" GodotInputEventScreenDrag
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenDrag_get_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventScreenTouch = GodotInputEventScreenTouch GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotInputEventScreenTouch where
        type BaseClass GodotInputEventScreenTouch = GodotInputEvent
        super = coerce
bindInputEventScreenTouch_is_pressed
  = unsafePerformIO $
      withCString "InputEventScreenTouch" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenTouch_is_pressed #-}

instance Method "is_pressed" GodotInputEventScreenTouch (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenTouch_is_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenTouch_set_index
  = unsafePerformIO $
      withCString "InputEventScreenTouch" $
        \ clsNamePtr ->
          withCString "set_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenTouch_set_index #-}

instance Method "set_index" GodotInputEventScreenTouch
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenTouch_set_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenTouch_get_index
  = unsafePerformIO $
      withCString "InputEventScreenTouch" $
        \ clsNamePtr ->
          withCString "get_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenTouch_get_index #-}

instance Method "get_index" GodotInputEventScreenTouch (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenTouch_get_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenTouch_set_position
  = unsafePerformIO $
      withCString "InputEventScreenTouch" $
        \ clsNamePtr ->
          withCString "set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenTouch_set_position #-}

instance Method "set_position" GodotInputEventScreenTouch
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenTouch_set_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenTouch_get_position
  = unsafePerformIO $
      withCString "InputEventScreenTouch" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenTouch_get_position #-}

instance Method "get_position" GodotInputEventScreenTouch
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenTouch_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventScreenTouch_set_pressed
  = unsafePerformIO $
      withCString "InputEventScreenTouch" $
        \ clsNamePtr ->
          withCString "set_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventScreenTouch_set_pressed #-}

instance Method "set_pressed" GodotInputEventScreenTouch
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventScreenTouch_set_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventAction = GodotInputEventAction GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotInputEventAction where
        type BaseClass GodotInputEventAction = GodotInputEvent
        super = coerce
bindInputEventAction_is_pressed
  = unsafePerformIO $
      withCString "InputEventAction" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventAction_is_pressed #-}

instance Method "is_pressed" GodotInputEventAction (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventAction_is_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventAction_set_action
  = unsafePerformIO $
      withCString "InputEventAction" $
        \ clsNamePtr ->
          withCString "set_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventAction_set_action #-}

instance Method "set_action" GodotInputEventAction
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventAction_set_action (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventAction_get_action
  = unsafePerformIO $
      withCString "InputEventAction" $
        \ clsNamePtr ->
          withCString "get_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventAction_get_action #-}

instance Method "get_action" GodotInputEventAction (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventAction_get_action (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventAction_set_pressed
  = unsafePerformIO $
      withCString "InputEventAction" $
        \ clsNamePtr ->
          withCString "set_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventAction_set_pressed #-}

instance Method "set_pressed" GodotInputEventAction (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventAction_set_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventGesture = GodotInputEventGesture GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotInputEventGesture where
        type BaseClass GodotInputEventGesture =
             GodotInputEventWithModifiers
        super = coerce
bindInputEventGesture_set_position
  = unsafePerformIO $
      withCString "InputEventGesture" $
        \ clsNamePtr ->
          withCString "set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventGesture_set_position #-}

instance Method "set_position" GodotInputEventGesture
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventGesture_set_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventGesture_get_position
  = unsafePerformIO $
      withCString "InputEventGesture" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventGesture_get_position #-}

instance Method "get_position" GodotInputEventGesture
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventGesture_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventMagnifyGesture = GodotInputEventMagnifyGesture GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotInputEventMagnifyGesture where
        type BaseClass GodotInputEventMagnifyGesture =
             GodotInputEventGesture
        super = coerce
bindInputEventMagnifyGesture_set_factor
  = unsafePerformIO $
      withCString "InputEventMagnifyGesture" $
        \ clsNamePtr ->
          withCString "set_factor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMagnifyGesture_set_factor #-}

instance Method "set_factor" GodotInputEventMagnifyGesture
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMagnifyGesture_set_factor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventMagnifyGesture_get_factor
  = unsafePerformIO $
      withCString "InputEventMagnifyGesture" $
        \ clsNamePtr ->
          withCString "get_factor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventMagnifyGesture_get_factor #-}

instance Method "get_factor" GodotInputEventMagnifyGesture
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventMagnifyGesture_get_factor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputEventPanGesture = GodotInputEventPanGesture GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotInputEventPanGesture where
        type BaseClass GodotInputEventPanGesture = GodotInputEventGesture
        super = coerce
bindInputEventPanGesture_set_delta
  = unsafePerformIO $
      withCString "InputEventPanGesture" $
        \ clsNamePtr ->
          withCString "set_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventPanGesture_set_delta #-}

instance Method "set_delta" GodotInputEventPanGesture
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventPanGesture_set_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputEventPanGesture_get_delta
  = unsafePerformIO $
      withCString "InputEventPanGesture" $
        \ clsNamePtr ->
          withCString "get_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputEventPanGesture_get_delta #-}

instance Method "get_delta" GodotInputEventPanGesture
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputEventPanGesture_get_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotFuncRef = GodotFuncRef GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotFuncRef where
        type BaseClass GodotFuncRef = GodotReference
        super = coerce
bindFuncRef_set_instance
  = unsafePerformIO $
      withCString "FuncRef" $
        \ clsNamePtr ->
          withCString "set_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFuncRef_set_instance #-}

instance Method "set_instance" GodotFuncRef (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFuncRef_set_instance (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFuncRef_set_function
  = unsafePerformIO $
      withCString "FuncRef" $
        \ clsNamePtr ->
          withCString "set_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFuncRef_set_function #-}

instance Method "set_function" GodotFuncRef (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFuncRef_set_function (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStreamPeer = GodotStreamPeer GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotStreamPeer where
        type BaseClass GodotStreamPeer = GodotReference
        super = coerce
bindStreamPeer_put_data
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_data #-}

instance Method "put_data" GodotStreamPeer
           (GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_data (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_partial_data
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_partial_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_partial_data #-}

instance Method "put_partial_data" GodotStreamPeer
           (GodotPoolByteArray -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_partial_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_data
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_data #-}

instance Method "get_data" GodotStreamPeer (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_data (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_partial_data
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_partial_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_partial_data #-}

instance Method "get_partial_data" GodotStreamPeer
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_partial_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_available_bytes
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_available_bytes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_available_bytes #-}

instance Method "get_available_bytes" GodotStreamPeer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_available_bytes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_set_big_endian
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "set_big_endian" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_set_big_endian #-}

instance Method "set_big_endian" GodotStreamPeer (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_set_big_endian (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_is_big_endian_enabled
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "is_big_endian_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_is_big_endian_enabled #-}

instance Method "is_big_endian_enabled" GodotStreamPeer (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_is_big_endian_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_8
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_8" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_8 #-}

instance Method "put_8" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_8 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_u8
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_u8" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_u8 #-}

instance Method "put_u8" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_u8 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_16
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_16" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_16 #-}

instance Method "put_16" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_16 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_u16
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_u16" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_u16 #-}

instance Method "put_u16" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_u16 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_32
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_32" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_32 #-}

instance Method "put_32" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_32 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_u32
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_u32" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_u32 #-}

instance Method "put_u32" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_u32 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_64
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_64 #-}

instance Method "put_64" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_64 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_u64
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_u64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_u64 #-}

instance Method "put_u64" GodotStreamPeer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_u64 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_float
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_float" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_float #-}

instance Method "put_float" GodotStreamPeer (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_float (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_double
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_double" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_double #-}

instance Method "put_double" GodotStreamPeer (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_double (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_string
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_string #-}

instance Method "put_string" GodotStreamPeer (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_utf8_string
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_utf8_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_utf8_string #-}

instance Method "put_utf8_string" GodotStreamPeer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_utf8_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_put_var
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "put_var" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_put_var #-}

instance Method "put_var" GodotStreamPeer (GodotVariant -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_put_var (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_8
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_8" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_8 #-}

instance Method "get_8" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_8 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_u8
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_u8" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_u8 #-}

instance Method "get_u8" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_u8 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_16
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_16" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_16 #-}

instance Method "get_16" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_16 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_u16
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_u16" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_u16 #-}

instance Method "get_u16" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_u16 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_32
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_32" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_32 #-}

instance Method "get_32" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_32 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_u32
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_u32" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_u32 #-}

instance Method "get_u32" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_u32 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_64
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_64 #-}

instance Method "get_64" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_64 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_u64
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_u64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_u64 #-}

instance Method "get_u64" GodotStreamPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_u64 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_float
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_float" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_float #-}

instance Method "get_float" GodotStreamPeer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_float (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_double
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_double" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_double #-}

instance Method "get_double" GodotStreamPeer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_double (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_string
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_string #-}

instance Method "get_string" GodotStreamPeer
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_utf8_string
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_utf8_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_utf8_string #-}

instance Method "get_utf8_string" GodotStreamPeer
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_utf8_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeer_get_var
  = unsafePerformIO $
      withCString "StreamPeer" $
        \ clsNamePtr ->
          withCString "get_var" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeer_get_var #-}

instance Method "get_var" GodotStreamPeer (IO GodotVariant) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeer_get_var (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStreamPeerBuffer = GodotStreamPeerBuffer GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotStreamPeerBuffer where
        type BaseClass GodotStreamPeerBuffer = GodotStreamPeer
        super = coerce
bindStreamPeerBuffer_seek
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_seek #-}

instance Method "seek" GodotStreamPeerBuffer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_seek (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerBuffer_get_size
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_get_size #-}

instance Method "get_size" GodotStreamPeerBuffer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_get_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerBuffer_get_position
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_get_position #-}

instance Method "get_position" GodotStreamPeerBuffer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerBuffer_resize
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "resize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_resize #-}

instance Method "resize" GodotStreamPeerBuffer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_resize (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerBuffer_set_data_array
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "set_data_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_set_data_array #-}

instance Method "set_data_array" GodotStreamPeerBuffer
           (GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_set_data_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerBuffer_get_data_array
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "get_data_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_get_data_array #-}

instance Method "get_data_array" GodotStreamPeerBuffer
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_get_data_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerBuffer_clear
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_clear #-}

instance Method "clear" GodotStreamPeerBuffer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_clear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerBuffer_duplicate
  = unsafePerformIO $
      withCString "StreamPeerBuffer" $
        \ clsNamePtr ->
          withCString "duplicate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerBuffer_duplicate #-}

instance Method "duplicate" GodotStreamPeerBuffer
           (IO GodotStreamPeerBuffer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerBuffer_duplicate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStreamPeerTCP = GodotStreamPeerTCP GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotStreamPeerTCP where
        type BaseClass GodotStreamPeerTCP = GodotStreamPeer
        super = coerce
bindStreamPeerTCP_connect_to_host
  = unsafePerformIO $
      withCString "StreamPeerTCP" $
        \ clsNamePtr ->
          withCString "connect_to_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerTCP_connect_to_host #-}

instance Method "connect_to_host" GodotStreamPeerTCP
           (GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerTCP_connect_to_host
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerTCP_is_connected_to_host
  = unsafePerformIO $
      withCString "StreamPeerTCP" $
        \ clsNamePtr ->
          withCString "is_connected_to_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerTCP_is_connected_to_host #-}

instance Method "is_connected_to_host" GodotStreamPeerTCP (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerTCP_is_connected_to_host
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerTCP_get_status
  = unsafePerformIO $
      withCString "StreamPeerTCP" $
        \ clsNamePtr ->
          withCString "get_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerTCP_get_status #-}

instance Method "get_status" GodotStreamPeerTCP (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerTCP_get_status (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerTCP_get_connected_host
  = unsafePerformIO $
      withCString "StreamPeerTCP" $
        \ clsNamePtr ->
          withCString "get_connected_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerTCP_get_connected_host #-}

instance Method "get_connected_host" GodotStreamPeerTCP
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerTCP_get_connected_host
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerTCP_get_connected_port
  = unsafePerformIO $
      withCString "StreamPeerTCP" $
        \ clsNamePtr ->
          withCString "get_connected_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerTCP_get_connected_port #-}

instance Method "get_connected_port" GodotStreamPeerTCP (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerTCP_get_connected_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerTCP_disconnect_from_host
  = unsafePerformIO $
      withCString "StreamPeerTCP" $
        \ clsNamePtr ->
          withCString "disconnect_from_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerTCP_disconnect_from_host #-}

instance Method "disconnect_from_host" GodotStreamPeerTCP (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerTCP_disconnect_from_host
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerTCP_set_no_delay
  = unsafePerformIO $
      withCString "StreamPeerTCP" $
        \ clsNamePtr ->
          withCString "set_no_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerTCP_set_no_delay #-}

instance Method "set_no_delay" GodotStreamPeerTCP (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerTCP_set_no_delay (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTCP_Server = GodotTCP_Server GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotTCP_Server where
        type BaseClass GodotTCP_Server = GodotReference
        super = coerce
bindTCP_Server_listen
  = unsafePerformIO $
      withCString "TCP_Server" $
        \ clsNamePtr ->
          withCString "listen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTCP_Server_listen #-}

instance Method "listen" GodotTCP_Server
           (Int -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTCP_Server_listen (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTCP_Server_is_connection_available
  = unsafePerformIO $
      withCString "TCP_Server" $
        \ clsNamePtr ->
          withCString "is_connection_available" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTCP_Server_is_connection_available #-}

instance Method "is_connection_available" GodotTCP_Server (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTCP_Server_is_connection_available
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTCP_Server_take_connection
  = unsafePerformIO $
      withCString "TCP_Server" $
        \ clsNamePtr ->
          withCString "take_connection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTCP_Server_take_connection #-}

instance Method "take_connection" GodotTCP_Server
           (IO GodotStreamPeerTCP)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTCP_Server_take_connection (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTCP_Server_stop
  = unsafePerformIO $
      withCString "TCP_Server" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTCP_Server_stop #-}

instance Method "stop" GodotTCP_Server (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTCP_Server_stop (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPacketPeer = GodotPacketPeer GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotPacketPeer where
        type BaseClass GodotPacketPeer = GodotReference
        super = coerce
bindPacketPeer_get_var
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "get_var" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_get_var #-}

instance Method "get_var" GodotPacketPeer (IO GodotVariant) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_get_var (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeer_put_var
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "put_var" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_put_var #-}

instance Method "put_var" GodotPacketPeer (GodotVariant -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_put_var (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeer_get_packet
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "get_packet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_get_packet #-}

instance Method "get_packet" GodotPacketPeer
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_get_packet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeer_put_packet
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "put_packet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_put_packet #-}

instance Method "put_packet" GodotPacketPeer
           (GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_put_packet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeer_get_packet_error
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "get_packet_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_get_packet_error #-}

instance Method "get_packet_error" GodotPacketPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_get_packet_error (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeer_get_available_packet_count
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "get_available_packet_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_get_available_packet_count #-}

instance Method "get_available_packet_count" GodotPacketPeer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_get_available_packet_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeer_set_allow_object_decoding
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "set_allow_object_decoding" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_set_allow_object_decoding #-}

instance Method "set_allow_object_decoding" GodotPacketPeer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_set_allow_object_decoding
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeer_is_object_decoding_allowed
  = unsafePerformIO $
      withCString "PacketPeer" $
        \ clsNamePtr ->
          withCString "is_object_decoding_allowed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeer_is_object_decoding_allowed #-}

instance Method "is_object_decoding_allowed" GodotPacketPeer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeer_is_object_decoding_allowed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPacketPeerUDP = GodotPacketPeerUDP GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotPacketPeerUDP where
        type BaseClass GodotPacketPeerUDP = GodotPacketPeer
        super = coerce
bindPacketPeerUDP_listen
  = unsafePerformIO $
      withCString "PacketPeerUDP" $
        \ clsNamePtr ->
          withCString "listen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerUDP_listen #-}

instance Method "listen" GodotPacketPeerUDP
           (Int -> GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerUDP_listen (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerUDP_close
  = unsafePerformIO $
      withCString "PacketPeerUDP" $
        \ clsNamePtr ->
          withCString "close" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerUDP_close #-}

instance Method "close" GodotPacketPeerUDP (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerUDP_close (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerUDP_wait
  = unsafePerformIO $
      withCString "PacketPeerUDP" $
        \ clsNamePtr ->
          withCString "wait" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerUDP_wait #-}

instance Method "wait" GodotPacketPeerUDP (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerUDP_wait (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerUDP_is_listening
  = unsafePerformIO $
      withCString "PacketPeerUDP" $
        \ clsNamePtr ->
          withCString "is_listening" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerUDP_is_listening #-}

instance Method "is_listening" GodotPacketPeerUDP (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerUDP_is_listening (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerUDP_get_packet_ip
  = unsafePerformIO $
      withCString "PacketPeerUDP" $
        \ clsNamePtr ->
          withCString "get_packet_ip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerUDP_get_packet_ip #-}

instance Method "get_packet_ip" GodotPacketPeerUDP (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerUDP_get_packet_ip (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerUDP_get_packet_port
  = unsafePerformIO $
      withCString "PacketPeerUDP" $
        \ clsNamePtr ->
          withCString "get_packet_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerUDP_get_packet_port #-}

instance Method "get_packet_port" GodotPacketPeerUDP (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerUDP_get_packet_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerUDP_set_dest_address
  = unsafePerformIO $
      withCString "PacketPeerUDP" $
        \ clsNamePtr ->
          withCString "set_dest_address" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerUDP_set_dest_address #-}

instance Method "set_dest_address" GodotPacketPeerUDP
           (GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerUDP_set_dest_address
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStreamPeerSSL = GodotStreamPeerSSL GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotStreamPeerSSL where
        type BaseClass GodotStreamPeerSSL = GodotStreamPeer
        super = coerce
bindStreamPeerSSL_poll
  = unsafePerformIO $
      withCString "StreamPeerSSL" $
        \ clsNamePtr ->
          withCString "poll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerSSL_poll #-}

instance Method "poll" GodotStreamPeerSSL (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerSSL_poll (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerSSL_accept_stream
  = unsafePerformIO $
      withCString "StreamPeerSSL" $
        \ clsNamePtr ->
          withCString "accept_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerSSL_accept_stream #-}

instance Method "accept_stream" GodotStreamPeerSSL
           (GodotStreamPeer -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerSSL_accept_stream (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerSSL_connect_to_stream
  = unsafePerformIO $
      withCString "StreamPeerSSL" $
        \ clsNamePtr ->
          withCString "connect_to_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerSSL_connect_to_stream #-}

instance Method "connect_to_stream" GodotStreamPeerSSL
           (GodotStreamPeer -> Bool -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerSSL_connect_to_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerSSL_get_status
  = unsafePerformIO $
      withCString "StreamPeerSSL" $
        \ clsNamePtr ->
          withCString "get_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerSSL_get_status #-}

instance Method "get_status" GodotStreamPeerSSL (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerSSL_get_status (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerSSL_disconnect_from_stream
  = unsafePerformIO $
      withCString "StreamPeerSSL" $
        \ clsNamePtr ->
          withCString "disconnect_from_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerSSL_disconnect_from_stream #-}

instance Method "disconnect_from_stream" GodotStreamPeerSSL (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamPeerSSL_disconnect_from_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerSSL_set_blocking_handshake_enabled
  = unsafePerformIO $
      withCString "StreamPeerSSL" $
        \ clsNamePtr ->
          withCString "set_blocking_handshake_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerSSL_set_blocking_handshake_enabled #-}

instance Method "set_blocking_handshake_enabled" GodotStreamPeerSSL
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStreamPeerSSL_set_blocking_handshake_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamPeerSSL_is_blocking_handshake_enabled
  = unsafePerformIO $
      withCString "StreamPeerSSL" $
        \ clsNamePtr ->
          withCString "is_blocking_handshake_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamPeerSSL_is_blocking_handshake_enabled #-}

instance Method "is_blocking_handshake_enabled" GodotStreamPeerSSL
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStreamPeerSSL_is_blocking_handshake_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotIP = GodotIP GodotObject
                    deriving newtype AsVariant

instance HasBaseClass GodotIP where
        type BaseClass GodotIP = GodotObject
        super = coerce
bindIP_resolve_hostname
  = unsafePerformIO $
      withCString "IP" $
        \ clsNamePtr ->
          withCString "resolve_hostname" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindIP_resolve_hostname #-}

instance Method "resolve_hostname" GodotIP
           (GodotString -> Int -> IO GodotString)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindIP_resolve_hostname (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindIP_resolve_hostname_queue_item
  = unsafePerformIO $
      withCString "IP" $
        \ clsNamePtr ->
          withCString "resolve_hostname_queue_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindIP_resolve_hostname_queue_item #-}

instance Method "resolve_hostname_queue_item" GodotIP
           (GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindIP_resolve_hostname_queue_item
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindIP_get_resolve_item_status
  = unsafePerformIO $
      withCString "IP" $
        \ clsNamePtr ->
          withCString "get_resolve_item_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindIP_get_resolve_item_status #-}

instance Method "get_resolve_item_status" GodotIP (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindIP_get_resolve_item_status (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindIP_get_resolve_item_address
  = unsafePerformIO $
      withCString "IP" $
        \ clsNamePtr ->
          withCString "get_resolve_item_address" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindIP_get_resolve_item_address #-}

instance Method "get_resolve_item_address" GodotIP
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindIP_get_resolve_item_address (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindIP_erase_resolve_item
  = unsafePerformIO $
      withCString "IP" $
        \ clsNamePtr ->
          withCString "erase_resolve_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindIP_erase_resolve_item #-}

instance Method "erase_resolve_item" GodotIP (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindIP_erase_resolve_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindIP_get_local_addresses
  = unsafePerformIO $
      withCString "IP" $
        \ clsNamePtr ->
          withCString "get_local_addresses" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindIP_get_local_addresses #-}

instance Method "get_local_addresses" GodotIP (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindIP_get_local_addresses (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindIP_clear_cache
  = unsafePerformIO $
      withCString "IP" $
        \ clsNamePtr ->
          withCString "clear_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindIP_clear_cache #-}

instance Method "clear_cache" GodotIP (GodotString -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindIP_clear_cache (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPacketPeerStream = GodotPacketPeerStream GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotPacketPeerStream where
        type BaseClass GodotPacketPeerStream = GodotPacketPeer
        super = coerce
bindPacketPeerStream_set_stream_peer
  = unsafePerformIO $
      withCString "PacketPeerStream" $
        \ clsNamePtr ->
          withCString "set_stream_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerStream_set_stream_peer #-}

instance Method "set_stream_peer" GodotPacketPeerStream
           (GodotStreamPeer -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerStream_set_stream_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerStream_get_stream_peer
  = unsafePerformIO $
      withCString "PacketPeerStream" $
        \ clsNamePtr ->
          withCString "get_stream_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerStream_get_stream_peer #-}

instance Method "get_stream_peer" GodotPacketPeerStream
           (IO GodotStreamPeer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPacketPeerStream_get_stream_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerStream_set_input_buffer_max_size
  = unsafePerformIO $
      withCString "PacketPeerStream" $
        \ clsNamePtr ->
          withCString "set_input_buffer_max_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerStream_set_input_buffer_max_size #-}

instance Method "set_input_buffer_max_size" GodotPacketPeerStream
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPacketPeerStream_set_input_buffer_max_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerStream_set_output_buffer_max_size
  = unsafePerformIO $
      withCString "PacketPeerStream" $
        \ clsNamePtr ->
          withCString "set_output_buffer_max_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerStream_set_output_buffer_max_size #-}

instance Method "set_output_buffer_max_size" GodotPacketPeerStream
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPacketPeerStream_set_output_buffer_max_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerStream_get_input_buffer_max_size
  = unsafePerformIO $
      withCString "PacketPeerStream" $
        \ clsNamePtr ->
          withCString "get_input_buffer_max_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerStream_get_input_buffer_max_size #-}

instance Method "get_input_buffer_max_size" GodotPacketPeerStream
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPacketPeerStream_get_input_buffer_max_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPacketPeerStream_get_output_buffer_max_size
  = unsafePerformIO $
      withCString "PacketPeerStream" $
        \ clsNamePtr ->
          withCString "get_output_buffer_max_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPacketPeerStream_get_output_buffer_max_size #-}

instance Method "get_output_buffer_max_size" GodotPacketPeerStream
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPacketPeerStream_get_output_buffer_max_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNetworkedMultiplayerPeer = GodotNetworkedMultiplayerPeer GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotNetworkedMultiplayerPeer where
        type BaseClass GodotNetworkedMultiplayerPeer = GodotPacketPeer
        super = coerce
bindNetworkedMultiplayerPeer_set_transfer_mode
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "set_transfer_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_set_transfer_mode #-}

instance Method "set_transfer_mode" GodotNetworkedMultiplayerPeer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerPeer_set_transfer_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_get_transfer_mode
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "get_transfer_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_get_transfer_mode #-}

instance Method "get_transfer_mode" GodotNetworkedMultiplayerPeer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerPeer_get_transfer_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_set_target_peer
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "set_target_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_set_target_peer #-}

instance Method "set_target_peer" GodotNetworkedMultiplayerPeer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerPeer_set_target_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_get_packet_peer
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "get_packet_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_get_packet_peer #-}

instance Method "get_packet_peer" GodotNetworkedMultiplayerPeer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerPeer_get_packet_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_poll
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "poll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_poll #-}

instance Method "poll" GodotNetworkedMultiplayerPeer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerPeer_poll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_get_connection_status
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "get_connection_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_get_connection_status #-}

instance Method "get_connection_status"
           GodotNetworkedMultiplayerPeer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerPeer_get_connection_status
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_get_unique_id
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "get_unique_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_get_unique_id #-}

instance Method "get_unique_id" GodotNetworkedMultiplayerPeer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerPeer_get_unique_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_set_refuse_new_connections
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "set_refuse_new_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_set_refuse_new_connections
             #-}

instance Method "set_refuse_new_connections"
           GodotNetworkedMultiplayerPeer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerPeer_set_refuse_new_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerPeer_is_refusing_new_connections
  = unsafePerformIO $
      withCString "NetworkedMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "is_refusing_new_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerPeer_is_refusing_new_connections
             #-}

instance Method "is_refusing_new_connections"
           GodotNetworkedMultiplayerPeer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerPeer_is_refusing_new_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMultiplayerAPI = GodotMultiplayerAPI GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotMultiplayerAPI where
        type BaseClass GodotMultiplayerAPI = GodotReference
        super = coerce
bindMultiplayerAPI_set_root_node
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "set_root_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_set_root_node #-}

instance Method "set_root_node" GodotMultiplayerAPI
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_set_root_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_send_bytes
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "send_bytes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_send_bytes #-}

instance Method "send_bytes" GodotMultiplayerAPI
           (GodotPoolByteArray -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_send_bytes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_has_network_peer
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "has_network_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_has_network_peer #-}

instance Method "has_network_peer" GodotMultiplayerAPI (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_has_network_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_get_network_peer
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "get_network_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_get_network_peer #-}

instance Method "get_network_peer" GodotMultiplayerAPI
           (IO GodotNetworkedMultiplayerPeer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_get_network_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_get_network_unique_id
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "get_network_unique_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_get_network_unique_id #-}

instance Method "get_network_unique_id" GodotMultiplayerAPI
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_get_network_unique_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_is_network_server
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "is_network_server" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_is_network_server #-}

instance Method "is_network_server" GodotMultiplayerAPI (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_is_network_server
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_get_rpc_sender_id
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "get_rpc_sender_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_get_rpc_sender_id #-}

instance Method "get_rpc_sender_id" GodotMultiplayerAPI (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_get_rpc_sender_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI__add_peer
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "_add_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI__add_peer #-}

instance Method "_add_peer" GodotMultiplayerAPI (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI__add_peer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI__del_peer
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "_del_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI__del_peer #-}

instance Method "_del_peer" GodotMultiplayerAPI (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI__del_peer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_set_network_peer
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "set_network_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_set_network_peer #-}

instance Method "set_network_peer" GodotMultiplayerAPI
           (GodotNetworkedMultiplayerPeer -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_set_network_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_poll
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "poll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_poll #-}

instance Method "poll" GodotMultiplayerAPI (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_poll (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_clear
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_clear #-}

instance Method "clear" GodotMultiplayerAPI (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI__connected_to_server
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "_connected_to_server" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI__connected_to_server #-}

instance Method "_connected_to_server" GodotMultiplayerAPI (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI__connected_to_server
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI__connection_failed
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "_connection_failed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI__connection_failed #-}

instance Method "_connection_failed" GodotMultiplayerAPI (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI__connection_failed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI__server_disconnected
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "_server_disconnected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI__server_disconnected #-}

instance Method "_server_disconnected" GodotMultiplayerAPI (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiplayerAPI__server_disconnected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_get_network_connected_peers
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "get_network_connected_peers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_get_network_connected_peers #-}

instance Method "get_network_connected_peers" GodotMultiplayerAPI
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindMultiplayerAPI_get_network_connected_peers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_set_refuse_new_network_connections
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "set_refuse_new_network_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_set_refuse_new_network_connections
             #-}

instance Method "set_refuse_new_network_connections"
           GodotMultiplayerAPI
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindMultiplayerAPI_set_refuse_new_network_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiplayerAPI_is_refusing_new_network_connections
  = unsafePerformIO $
      withCString "MultiplayerAPI" $
        \ clsNamePtr ->
          withCString "is_refusing_new_network_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiplayerAPI_is_refusing_new_network_connections
             #-}

instance Method "is_refusing_new_network_connections"
           GodotMultiplayerAPI
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindMultiplayerAPI_is_refusing_new_network_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMainLoop = GodotMainLoop GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotMainLoop where
        type BaseClass GodotMainLoop = GodotObject
        super = coerce
bindMainLoop__input_event
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "_input_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop__input_event #-}

instance Method "_input_event" GodotMainLoop
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop__input_event (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop__input_text
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "_input_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop__input_text #-}

instance Method "_input_text" GodotMainLoop (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop__input_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop__initialize
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "_initialize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop__initialize #-}

instance Method "_initialize" GodotMainLoop (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop__initialize (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop__iteration
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "_iteration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop__iteration #-}

instance Method "_iteration" GodotMainLoop (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop__iteration (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop__idle
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "_idle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop__idle #-}

instance Method "_idle" GodotMainLoop (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop__idle (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop__drop_files
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "_drop_files" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop__drop_files #-}

instance Method "_drop_files" GodotMainLoop
           (GodotPoolStringArray -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop__drop_files (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop__finalize
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "_finalize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop__finalize #-}

instance Method "_finalize" GodotMainLoop (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop__finalize (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop_input_event
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "input_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop_input_event #-}

instance Method "input_event" GodotMainLoop
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop_input_event (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop_input_text
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "input_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop_input_text #-}

instance Method "input_text" GodotMainLoop (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop_input_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop_init
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "init" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop_init #-}

instance Method "init" GodotMainLoop (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop_init (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop_iteration
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "iteration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop_iteration #-}

instance Method "iteration" GodotMainLoop (Float -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop_iteration (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop_idle
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "idle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop_idle #-}

instance Method "idle" GodotMainLoop (Float -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop_idle (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMainLoop_finish
  = unsafePerformIO $
      withCString "MainLoop" $
        \ clsNamePtr ->
          withCString "finish" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMainLoop_finish #-}

instance Method "finish" GodotMainLoop (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMainLoop_finish (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTranslation = GodotTranslation GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotTranslation where
        type BaseClass GodotTranslation = GodotResource
        super = coerce
bindTranslation_set_locale
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "set_locale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation_set_locale #-}

instance Method "set_locale" GodotTranslation
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation_set_locale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation_get_locale
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "get_locale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation_get_locale #-}

instance Method "get_locale" GodotTranslation (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation_get_locale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation_add_message
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "add_message" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation_add_message #-}

instance Method "add_message" GodotTranslation
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation_add_message (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation_get_message
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "get_message" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation_get_message #-}

instance Method "get_message" GodotTranslation
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation_get_message (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation_erase_message
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "erase_message" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation_erase_message #-}

instance Method "erase_message" GodotTranslation
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation_erase_message (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation_get_message_list
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "get_message_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation_get_message_list #-}

instance Method "get_message_list" GodotTranslation
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation_get_message_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation_get_message_count
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "get_message_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation_get_message_count #-}

instance Method "get_message_count" GodotTranslation (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation_get_message_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation__set_messages
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "_set_messages" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation__set_messages #-}

instance Method "_set_messages" GodotTranslation
           (GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation__set_messages (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslation__get_messages
  = unsafePerformIO $
      withCString "Translation" $
        \ clsNamePtr ->
          withCString "_get_messages" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslation__get_messages #-}

instance Method "_get_messages" GodotTranslation
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslation__get_messages (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPHashTranslation = GodotPHashTranslation GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotPHashTranslation where
        type BaseClass GodotPHashTranslation = GodotTranslation
        super = coerce
bindPHashTranslation_generate
  = unsafePerformIO $
      withCString "PHashTranslation" $
        \ clsNamePtr ->
          withCString "generate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPHashTranslation_generate #-}

instance Method "generate" GodotPHashTranslation
           (GodotTranslation -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPHashTranslation_generate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotUndoRedo = GodotUndoRedo GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotUndoRedo where
        type BaseClass GodotUndoRedo = GodotObject
        super = coerce
bindUndoRedo_create_action
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "create_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_create_action #-}

instance Method "create_action" GodotUndoRedo
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_create_action (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_commit_action
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "commit_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_commit_action #-}

instance Method "commit_action" GodotUndoRedo (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_commit_action (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_add_do_property
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "add_do_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_add_do_property #-}

instance Method "add_do_property" GodotUndoRedo
           (GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_add_do_property (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_add_undo_property
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "add_undo_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_add_undo_property #-}

instance Method "add_undo_property" GodotUndoRedo
           (GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_add_undo_property (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_add_do_reference
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "add_do_reference" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_add_do_reference #-}

instance Method "add_do_reference" GodotUndoRedo
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_add_do_reference (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_add_undo_reference
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "add_undo_reference" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_add_undo_reference #-}

instance Method "add_undo_reference" GodotUndoRedo
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_add_undo_reference (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_clear_history
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "clear_history" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_clear_history #-}

instance Method "clear_history" GodotUndoRedo (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_clear_history (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_get_current_action_name
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "get_current_action_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_get_current_action_name #-}

instance Method "get_current_action_name" GodotUndoRedo
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_get_current_action_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_get_version
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "get_version" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_get_version #-}

instance Method "get_version" GodotUndoRedo (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_get_version (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_redo
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "redo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_redo #-}

instance Method "redo" GodotUndoRedo (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_redo (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUndoRedo_undo
  = unsafePerformIO $
      withCString "UndoRedo" $
        \ clsNamePtr ->
          withCString "undo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUndoRedo_undo #-}

instance Method "undo" GodotUndoRedo (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUndoRedo_undo (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotHTTPClient = GodotHTTPClient GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotHTTPClient where
        type BaseClass GodotHTTPClient = GodotReference
        super = coerce
bindHTTPClient_connect_to_host
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "connect_to_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_connect_to_host #-}

instance Method "connect_to_host" GodotHTTPClient
           (GodotString -> Int -> Bool -> Bool -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_connect_to_host (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_set_connection
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "set_connection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_set_connection #-}

instance Method "set_connection" GodotHTTPClient
           (GodotStreamPeer -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_set_connection (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_get_connection
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "get_connection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_get_connection #-}

instance Method "get_connection" GodotHTTPClient
           (IO GodotStreamPeer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_get_connection (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_request_raw
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "request_raw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_request_raw #-}

instance Method "request_raw" GodotHTTPClient
           (Int ->
              GodotString ->
                GodotPoolStringArray -> GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_request_raw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_request
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "request" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_request #-}

instance Method "request" GodotHTTPClient
           (Int ->
              GodotString -> GodotPoolStringArray -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_request (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_close
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "close" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_close #-}

instance Method "close" GodotHTTPClient (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_close (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_has_response
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "has_response" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_has_response #-}

instance Method "has_response" GodotHTTPClient (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_has_response (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_is_response_chunked
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "is_response_chunked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_is_response_chunked #-}

instance Method "is_response_chunked" GodotHTTPClient (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_is_response_chunked
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_get_response_code
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "get_response_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_get_response_code #-}

instance Method "get_response_code" GodotHTTPClient (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_get_response_code
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_get_response_headers
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "get_response_headers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_get_response_headers #-}

instance Method "get_response_headers" GodotHTTPClient
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_get_response_headers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_get_response_headers_as_dictionary
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "get_response_headers_as_dictionary" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_get_response_headers_as_dictionary #-}

instance Method "get_response_headers_as_dictionary"
           GodotHTTPClient
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindHTTPClient_get_response_headers_as_dictionary
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_get_response_body_length
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "get_response_body_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_get_response_body_length #-}

instance Method "get_response_body_length" GodotHTTPClient (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_get_response_body_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_read_response_body_chunk
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "read_response_body_chunk" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_read_response_body_chunk #-}

instance Method "read_response_body_chunk" GodotHTTPClient
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_read_response_body_chunk
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_set_read_chunk_size
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "set_read_chunk_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_set_read_chunk_size #-}

instance Method "set_read_chunk_size" GodotHTTPClient
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_set_read_chunk_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_set_blocking_mode
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "set_blocking_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_set_blocking_mode #-}

instance Method "set_blocking_mode" GodotHTTPClient (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_set_blocking_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_is_blocking_mode_enabled
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "is_blocking_mode_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_is_blocking_mode_enabled #-}

instance Method "is_blocking_mode_enabled" GodotHTTPClient
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_is_blocking_mode_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_get_status
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "get_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_get_status #-}

instance Method "get_status" GodotHTTPClient (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_get_status (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_poll
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "poll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_poll #-}

instance Method "poll" GodotHTTPClient (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_poll (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPClient_query_string_from_dict
  = unsafePerformIO $
      withCString "HTTPClient" $
        \ clsNamePtr ->
          withCString "query_string_from_dict" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPClient_query_string_from_dict #-}

instance Method "query_string_from_dict" GodotHTTPClient
           (GodotDictionary -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPClient_query_string_from_dict
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTriangleMesh = GodotTriangleMesh GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotTriangleMesh where
        type BaseClass GodotTriangleMesh = GodotReference
        super = coerce

newtype GodotResourceInteractiveLoader = GodotResourceInteractiveLoader GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotResourceInteractiveLoader where
        type BaseClass GodotResourceInteractiveLoader = GodotReference
        super = coerce
bindResourceInteractiveLoader_get_resource
  = unsafePerformIO $
      withCString "ResourceInteractiveLoader" $
        \ clsNamePtr ->
          withCString "get_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourceInteractiveLoader_get_resource #-}

instance Method "get_resource" GodotResourceInteractiveLoader
           (IO GodotResource)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourceInteractiveLoader_get_resource
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourceInteractiveLoader_poll
  = unsafePerformIO $
      withCString "ResourceInteractiveLoader" $
        \ clsNamePtr ->
          withCString "poll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourceInteractiveLoader_poll #-}

instance Method "poll" GodotResourceInteractiveLoader (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourceInteractiveLoader_poll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourceInteractiveLoader_wait
  = unsafePerformIO $
      withCString "ResourceInteractiveLoader" $
        \ clsNamePtr ->
          withCString "wait" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourceInteractiveLoader_wait #-}

instance Method "wait" GodotResourceInteractiveLoader (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourceInteractiveLoader_wait
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourceInteractiveLoader_get_stage
  = unsafePerformIO $
      withCString "ResourceInteractiveLoader" $
        \ clsNamePtr ->
          withCString "get_stage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourceInteractiveLoader_get_stage #-}

instance Method "get_stage" GodotResourceInteractiveLoader (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourceInteractiveLoader_get_stage
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourceInteractiveLoader_get_stage_count
  = unsafePerformIO $
      withCString "ResourceInteractiveLoader" $
        \ clsNamePtr ->
          withCString "get_stage_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourceInteractiveLoader_get_stage_count #-}

instance Method "get_stage_count" GodotResourceInteractiveLoader
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindResourceInteractiveLoader_get_stage_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_File = Godot_File GodotObject
                       deriving newtype AsVariant

instance HasBaseClass Godot_File where
        type BaseClass Godot_File = GodotReference
        super = coerce
bind_File_open_encrypted
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "open_encrypted" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_open_encrypted #-}

instance Method "open_encrypted" Godot_File
           (GodotString -> Int -> GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_open_encrypted (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_open_encrypted_with_pass
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "open_encrypted_with_pass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_open_encrypted_with_pass #-}

instance Method "open_encrypted_with_pass" Godot_File
           (GodotString -> Int -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_open_encrypted_with_pass
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_open_compressed
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "open_compressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_open_compressed #-}

instance Method "open_compressed" Godot_File
           (GodotString -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_open_compressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_open
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "open" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_open #-}

instance Method "open" Godot_File (GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_open (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_close
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "close" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_close #-}

instance Method "close" Godot_File (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_close (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_path
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_path #-}

instance Method "get_path" Godot_File (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_path (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_path_absolute
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_path_absolute" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_path_absolute #-}

instance Method "get_path_absolute" Godot_File (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_path_absolute (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_is_open
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "is_open" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_is_open #-}

instance Method "is_open" Godot_File (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_is_open (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_seek
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_seek #-}

instance Method "seek" Godot_File (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_seek (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_seek_end
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "seek_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_seek_end #-}

instance Method "seek_end" Godot_File (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_seek_end (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_position
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_position #-}

instance Method "get_position" Godot_File (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_position (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_len
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_len" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_len #-}

instance Method "get_len" Godot_File (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_len (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_eof_reached
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "eof_reached" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_eof_reached #-}

instance Method "eof_reached" Godot_File (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_eof_reached (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_8
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_8" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_8 #-}

instance Method "get_8" Godot_File (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_8 (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_16
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_16" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_16 #-}

instance Method "get_16" Godot_File (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_16 (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_32
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_32" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_32 #-}

instance Method "get_32" Godot_File (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_32 (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_64
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_64 #-}

instance Method "get_64" Godot_File (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_64 (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_float
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_float" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_float #-}

instance Method "get_float" Godot_File (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_float (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_double
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_double" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_double #-}

instance Method "get_double" Godot_File (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_double (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_real
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_real" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_real #-}

instance Method "get_real" Godot_File (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_real (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_buffer
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_buffer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_buffer #-}

instance Method "get_buffer" Godot_File
           (Int -> IO GodotPoolByteArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_buffer (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_line
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_line #-}

instance Method "get_line" Godot_File (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_line (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_as_text
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_as_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_as_text #-}

instance Method "get_as_text" Godot_File (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_as_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_md5
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_md5" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_md5 #-}

instance Method "get_md5" Godot_File
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_md5 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_sha256
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_sha256" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_sha256 #-}

instance Method "get_sha256" Godot_File
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_sha256 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_endian_swap
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_endian_swap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_endian_swap #-}

instance Method "get_endian_swap" Godot_File (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_endian_swap (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_set_endian_swap
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "set_endian_swap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_set_endian_swap #-}

instance Method "set_endian_swap" Godot_File (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_set_endian_swap (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_error
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_error #-}

instance Method "get_error" Godot_File (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_error (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_var
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_var" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_var #-}

instance Method "get_var" Godot_File (IO GodotVariant) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_var (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_csv_line
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_csv_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_csv_line #-}

instance Method "get_csv_line" Godot_File
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_csv_line (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_8
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_8" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_8 #-}

instance Method "store_8" Godot_File (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_8 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_16
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_16" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_16 #-}

instance Method "store_16" Godot_File (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_16 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_32
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_32" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_32 #-}

instance Method "store_32" Godot_File (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_32 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_64
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_64 #-}

instance Method "store_64" Godot_File (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_64 (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_float
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_float" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_float #-}

instance Method "store_float" Godot_File (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_float (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_double
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_double" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_double #-}

instance Method "store_double" Godot_File (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_double (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_real
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_real" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_real #-}

instance Method "store_real" Godot_File (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_real (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_buffer
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_buffer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_buffer #-}

instance Method "store_buffer" Godot_File
           (GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_buffer (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_line
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_line #-}

instance Method "store_line" Godot_File (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_line (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_string
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_string #-}

instance Method "store_string" Godot_File (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_string (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_var
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_var" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_var #-}

instance Method "store_var" Godot_File (GodotVariant -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_var (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_store_pascal_string
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "store_pascal_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_store_pascal_string #-}

instance Method "store_pascal_string" Godot_File
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_store_pascal_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_pascal_string
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_pascal_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_pascal_string #-}

instance Method "get_pascal_string" Godot_File (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_pascal_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_file_exists
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "file_exists" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_file_exists #-}

instance Method "file_exists" Godot_File (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_file_exists (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_File_get_modified_time
  = unsafePerformIO $
      withCString "_File" $
        \ clsNamePtr ->
          withCString "get_modified_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_File_get_modified_time #-}

instance Method "get_modified_time" Godot_File
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_File_get_modified_time (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_Directory = Godot_Directory GodotObject
                            deriving newtype AsVariant

instance HasBaseClass Godot_Directory where
        type BaseClass Godot_Directory = GodotReference
        super = coerce
bind_Directory_open
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "open" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_open #-}

instance Method "open" Godot_Directory (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_open (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_list_dir_begin
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "list_dir_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_list_dir_begin #-}

instance Method "list_dir_begin" Godot_Directory
           (Bool -> Bool -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_list_dir_begin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_get_next
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "get_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_get_next #-}

instance Method "get_next" Godot_Directory (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_get_next (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_current_is_dir
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "current_is_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_current_is_dir #-}

instance Method "current_is_dir" Godot_Directory (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_current_is_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_list_dir_end
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "list_dir_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_list_dir_end #-}

instance Method "list_dir_end" Godot_Directory (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_list_dir_end (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_get_drive_count
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "get_drive_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_get_drive_count #-}

instance Method "get_drive_count" Godot_Directory (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_get_drive_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_get_drive
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "get_drive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_get_drive #-}

instance Method "get_drive" Godot_Directory (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_get_drive (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_get_current_drive
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "get_current_drive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_get_current_drive #-}

instance Method "get_current_drive" Godot_Directory (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_get_current_drive
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_change_dir
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "change_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_change_dir #-}

instance Method "change_dir" Godot_Directory
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_change_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_get_current_dir
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "get_current_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_get_current_dir #-}

instance Method "get_current_dir" Godot_Directory (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_get_current_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_make_dir
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "make_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_make_dir #-}

instance Method "make_dir" Godot_Directory (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_make_dir (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_make_dir_recursive
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "make_dir_recursive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_make_dir_recursive #-}

instance Method "make_dir_recursive" Godot_Directory
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_make_dir_recursive
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_file_exists
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "file_exists" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_file_exists #-}

instance Method "file_exists" Godot_Directory
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_file_exists (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_dir_exists
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "dir_exists" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_dir_exists #-}

instance Method "dir_exists" Godot_Directory
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_dir_exists (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_get_space_left
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "get_space_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_get_space_left #-}

instance Method "get_space_left" Godot_Directory (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_get_space_left (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_copy
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "copy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_copy #-}

instance Method "copy" Godot_Directory
           (GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_copy (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_rename
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "rename" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_rename #-}

instance Method "rename" Godot_Directory
           (GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_rename (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Directory_remove
  = unsafePerformIO $
      withCString "_Directory" $
        \ clsNamePtr ->
          withCString "remove" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Directory_remove #-}

instance Method "remove" Godot_Directory (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Directory_remove (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_Thread = Godot_Thread GodotObject
                         deriving newtype AsVariant

instance HasBaseClass Godot_Thread where
        type BaseClass Godot_Thread = GodotReference
        super = coerce
bind_Thread_start
  = unsafePerformIO $
      withCString "_Thread" $
        \ clsNamePtr ->
          withCString "start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Thread_start #-}

instance Method "start" Godot_Thread
           (GodotObject -> GodotString -> GodotVariant -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Thread_start (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Thread_get_id
  = unsafePerformIO $
      withCString "_Thread" $
        \ clsNamePtr ->
          withCString "get_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Thread_get_id #-}

instance Method "get_id" Godot_Thread (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Thread_get_id (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Thread_is_active
  = unsafePerformIO $
      withCString "_Thread" $
        \ clsNamePtr ->
          withCString "is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Thread_is_active #-}

instance Method "is_active" Godot_Thread (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Thread_is_active (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Thread_wait_to_finish
  = unsafePerformIO $
      withCString "_Thread" $
        \ clsNamePtr ->
          withCString "wait_to_finish" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Thread_wait_to_finish #-}

instance Method "wait_to_finish" Godot_Thread (IO GodotVariant)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Thread_wait_to_finish (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_Mutex = Godot_Mutex GodotObject
                        deriving newtype AsVariant

instance HasBaseClass Godot_Mutex where
        type BaseClass Godot_Mutex = GodotReference
        super = coerce
bind_Mutex_lock
  = unsafePerformIO $
      withCString "_Mutex" $
        \ clsNamePtr ->
          withCString "lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Mutex_lock #-}

instance Method "lock" Godot_Mutex (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Mutex_lock (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Mutex_try_lock
  = unsafePerformIO $
      withCString "_Mutex" $
        \ clsNamePtr ->
          withCString "try_lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Mutex_try_lock #-}

instance Method "try_lock" Godot_Mutex (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Mutex_try_lock (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Mutex_unlock
  = unsafePerformIO $
      withCString "_Mutex" $
        \ clsNamePtr ->
          withCString "unlock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Mutex_unlock #-}

instance Method "unlock" Godot_Mutex (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Mutex_unlock (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_Semaphore = Godot_Semaphore GodotObject
                            deriving newtype AsVariant

instance HasBaseClass Godot_Semaphore where
        type BaseClass Godot_Semaphore = GodotReference
        super = coerce
bind_Semaphore_wait
  = unsafePerformIO $
      withCString "_Semaphore" $
        \ clsNamePtr ->
          withCString "wait" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Semaphore_wait #-}

instance Method "wait" Godot_Semaphore (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Semaphore_wait (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Semaphore_post
  = unsafePerformIO $
      withCString "_Semaphore" $
        \ clsNamePtr ->
          withCString "post" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Semaphore_post #-}

instance Method "post" Godot_Semaphore (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Semaphore_post (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotXMLParser = GodotXMLParser GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotXMLParser where
        type BaseClass GodotXMLParser = GodotReference
        super = coerce
bindXMLParser_read
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "read" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_read #-}

instance Method "read" GodotXMLParser (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_read (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_node_type
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_node_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_node_type #-}

instance Method "get_node_type" GodotXMLParser (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_node_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_node_name
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_node_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_node_name #-}

instance Method "get_node_name" GodotXMLParser (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_node_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_node_data
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_node_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_node_data #-}

instance Method "get_node_data" GodotXMLParser (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_node_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_node_offset
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_node_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_node_offset #-}

instance Method "get_node_offset" GodotXMLParser (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_node_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_attribute_count
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_attribute_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_attribute_count #-}

instance Method "get_attribute_count" GodotXMLParser (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_attribute_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_attribute_name
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_attribute_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_attribute_name #-}

instance Method "get_attribute_name" GodotXMLParser
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_attribute_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_attribute_value
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_attribute_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_attribute_value #-}

instance Method "get_attribute_value" GodotXMLParser
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_attribute_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_has_attribute
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "has_attribute" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_has_attribute #-}

instance Method "has_attribute" GodotXMLParser
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_has_attribute (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_named_attribute_value
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_named_attribute_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_named_attribute_value #-}

instance Method "get_named_attribute_value" GodotXMLParser
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_named_attribute_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_named_attribute_value_safe
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_named_attribute_value_safe" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_named_attribute_value_safe #-}

instance Method "get_named_attribute_value_safe" GodotXMLParser
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_named_attribute_value_safe
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_is_empty
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "is_empty" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_is_empty #-}

instance Method "is_empty" GodotXMLParser (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_is_empty (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_get_current_line
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "get_current_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_get_current_line #-}

instance Method "get_current_line" GodotXMLParser (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_get_current_line (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_skip_section
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "skip_section" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_skip_section #-}

instance Method "skip_section" GodotXMLParser (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_skip_section (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_seek
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_seek #-}

instance Method "seek" GodotXMLParser (Int -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_seek (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_open
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "open" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_open #-}

instance Method "open" GodotXMLParser (GodotString -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_open (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindXMLParser_open_buffer
  = unsafePerformIO $
      withCString "XMLParser" $
        \ clsNamePtr ->
          withCString "open_buffer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindXMLParser_open_buffer #-}

instance Method "open_buffer" GodotXMLParser
           (GodotPoolByteArray -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindXMLParser_open_buffer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotConfigFile = GodotConfigFile GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotConfigFile where
        type BaseClass GodotConfigFile = GodotReference
        super = coerce
bindConfigFile_set_value
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "set_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_set_value #-}

instance Method "set_value" GodotConfigFile
           (GodotString -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_set_value (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_get_value
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "get_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_get_value #-}

instance Method "get_value" GodotConfigFile
           (GodotString -> GodotString -> GodotVariant -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_get_value (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_has_section
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "has_section" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_has_section #-}

instance Method "has_section" GodotConfigFile
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_has_section (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_has_section_key
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "has_section_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_has_section_key #-}

instance Method "has_section_key" GodotConfigFile
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_has_section_key (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_get_sections
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "get_sections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_get_sections #-}

instance Method "get_sections" GodotConfigFile
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_get_sections (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_get_section_keys
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "get_section_keys" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_get_section_keys #-}

instance Method "get_section_keys" GodotConfigFile
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_get_section_keys (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_erase_section
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "erase_section" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_erase_section #-}

instance Method "erase_section" GodotConfigFile
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_erase_section (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_load
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "load" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_load #-}

instance Method "load" GodotConfigFile (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_load (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConfigFile_save
  = unsafePerformIO $
      withCString "ConfigFile" $
        \ clsNamePtr ->
          withCString "save" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfigFile_save #-}

instance Method "save" GodotConfigFile (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfigFile_save (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPCKPacker = GodotPCKPacker GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotPCKPacker where
        type BaseClass GodotPCKPacker = GodotReference
        super = coerce
bindPCKPacker_pck_start
  = unsafePerformIO $
      withCString "PCKPacker" $
        \ clsNamePtr ->
          withCString "pck_start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPCKPacker_pck_start #-}

instance Method "pck_start" GodotPCKPacker
           (GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPCKPacker_pck_start (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPCKPacker_add_file
  = unsafePerformIO $
      withCString "PCKPacker" $
        \ clsNamePtr ->
          withCString "add_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPCKPacker_add_file #-}

instance Method "add_file" GodotPCKPacker
           (GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPCKPacker_add_file (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPCKPacker_flush
  = unsafePerformIO $
      withCString "PCKPacker" $
        \ clsNamePtr ->
          withCString "flush" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPCKPacker_flush #-}

instance Method "flush" GodotPCKPacker (Bool -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPCKPacker_flush (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPackedDataContainer = GodotPackedDataContainer GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotPackedDataContainer where
        type BaseClass GodotPackedDataContainer = GodotResource
        super = coerce
bindPackedDataContainer__set_data
  = unsafePerformIO $
      withCString "PackedDataContainer" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainer__set_data #-}

instance Method "_set_data" GodotPackedDataContainer
           (GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainer__set_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainer__get_data
  = unsafePerformIO $
      withCString "PackedDataContainer" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainer__get_data #-}

instance Method "_get_data" GodotPackedDataContainer
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainer__get_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainer__iter_init
  = unsafePerformIO $
      withCString "PackedDataContainer" $
        \ clsNamePtr ->
          withCString "_iter_init" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainer__iter_init #-}

instance Method "_iter_init" GodotPackedDataContainer
           (GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainer__iter_init
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainer__iter_get
  = unsafePerformIO $
      withCString "PackedDataContainer" $
        \ clsNamePtr ->
          withCString "_iter_get" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainer__iter_get #-}

instance Method "_iter_get" GodotPackedDataContainer
           (GodotVariant -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainer__iter_get
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainer__iter_next
  = unsafePerformIO $
      withCString "PackedDataContainer" $
        \ clsNamePtr ->
          withCString "_iter_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainer__iter_next #-}

instance Method "_iter_next" GodotPackedDataContainer
           (GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainer__iter_next
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainer_pack
  = unsafePerformIO $
      withCString "PackedDataContainer" $
        \ clsNamePtr ->
          withCString "pack" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainer_pack #-}

instance Method "pack" GodotPackedDataContainer
           (GodotVariant -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainer_pack (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainer_size
  = unsafePerformIO $
      withCString "PackedDataContainer" $
        \ clsNamePtr ->
          withCString "size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainer_size #-}

instance Method "size" GodotPackedDataContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainer_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPackedDataContainerRef = GodotPackedDataContainerRef GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotPackedDataContainerRef where
        type BaseClass GodotPackedDataContainerRef = GodotReference
        super = coerce
bindPackedDataContainerRef_size
  = unsafePerformIO $
      withCString "PackedDataContainerRef" $
        \ clsNamePtr ->
          withCString "size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainerRef_size #-}

instance Method "size" GodotPackedDataContainerRef (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainerRef_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainerRef__iter_init
  = unsafePerformIO $
      withCString "PackedDataContainerRef" $
        \ clsNamePtr ->
          withCString "_iter_init" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainerRef__iter_init #-}

instance Method "_iter_init" GodotPackedDataContainerRef
           (GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainerRef__iter_init
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainerRef__iter_get
  = unsafePerformIO $
      withCString "PackedDataContainerRef" $
        \ clsNamePtr ->
          withCString "_iter_get" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainerRef__iter_get #-}

instance Method "_iter_get" GodotPackedDataContainerRef
           (GodotVariant -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainerRef__iter_get
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainerRef__iter_next
  = unsafePerformIO $
      withCString "PackedDataContainerRef" $
        \ clsNamePtr ->
          withCString "_iter_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainerRef__iter_next #-}

instance Method "_iter_next" GodotPackedDataContainerRef
           (GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainerRef__iter_next
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedDataContainerRef__is_dictionary
  = unsafePerformIO $
      withCString "PackedDataContainerRef" $
        \ clsNamePtr ->
          withCString "_is_dictionary" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedDataContainerRef__is_dictionary #-}

instance Method "_is_dictionary" GodotPackedDataContainerRef
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedDataContainerRef__is_dictionary
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAStar = GodotAStar GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotAStar where
        type BaseClass GodotAStar = GodotReference
        super = coerce
bindAStar__estimate_cost
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "_estimate_cost" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar__estimate_cost #-}

instance Method "_estimate_cost" GodotAStar
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar__estimate_cost (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar__compute_cost
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "_compute_cost" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar__compute_cost #-}

instance Method "_compute_cost" GodotAStar (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar__compute_cost (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_available_point_id
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_available_point_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_available_point_id #-}

instance Method "get_available_point_id" GodotAStar (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_available_point_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_add_point
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "add_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_add_point #-}

instance Method "add_point" GodotAStar
           (Int -> GodotVector3 -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_add_point (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_point_position
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_point_position #-}

instance Method "get_point_position" GodotAStar
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_set_point_position
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "set_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_set_point_position #-}

instance Method "set_point_position" GodotAStar
           (Int -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_set_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_point_weight_scale
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_point_weight_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_point_weight_scale #-}

instance Method "get_point_weight_scale" GodotAStar
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_point_weight_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_set_point_weight_scale
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "set_point_weight_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_set_point_weight_scale #-}

instance Method "set_point_weight_scale" GodotAStar
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_set_point_weight_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_remove_point
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "remove_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_remove_point #-}

instance Method "remove_point" GodotAStar (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_remove_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_has_point
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "has_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_has_point #-}

instance Method "has_point" GodotAStar (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_has_point (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_points
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_points #-}

instance Method "get_points" GodotAStar (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_points (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_point_connections
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_point_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_point_connections #-}

instance Method "get_point_connections" GodotAStar
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_point_connections (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_connect_points
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "connect_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_connect_points #-}

instance Method "connect_points" GodotAStar
           (Int -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_connect_points (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_disconnect_points
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "disconnect_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_disconnect_points #-}

instance Method "disconnect_points" GodotAStar
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_disconnect_points (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_are_points_connected
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "are_points_connected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_are_points_connected #-}

instance Method "are_points_connected" GodotAStar
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_are_points_connected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_clear
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_clear #-}

instance Method "clear" GodotAStar (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_clear (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_closest_point
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_closest_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_closest_point #-}

instance Method "get_closest_point" GodotAStar
           (GodotVector3 -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_closest_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_closest_position_in_segment
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_closest_position_in_segment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_closest_position_in_segment #-}

instance Method "get_closest_position_in_segment" GodotAStar
           (GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_closest_position_in_segment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_point_path
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_point_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_point_path #-}

instance Method "get_point_path" GodotAStar
           (Int -> Int -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_point_path (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAStar_get_id_path
  = unsafePerformIO $
      withCString "AStar" $
        \ clsNamePtr ->
          withCString "get_id_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAStar_get_id_path #-}

instance Method "get_id_path" GodotAStar
           (Int -> Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAStar_get_id_path (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEncodedObjectAsID = GodotEncodedObjectAsID GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotEncodedObjectAsID where
        type BaseClass GodotEncodedObjectAsID = GodotReference
        super = coerce
bindEncodedObjectAsID_set_object_id
  = unsafePerformIO $
      withCString "EncodedObjectAsID" $
        \ clsNamePtr ->
          withCString "set_object_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEncodedObjectAsID_set_object_id #-}

instance Method "set_object_id" GodotEncodedObjectAsID
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEncodedObjectAsID_set_object_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEncodedObjectAsID_get_object_id
  = unsafePerformIO $
      withCString "EncodedObjectAsID" $
        \ clsNamePtr ->
          withCString "get_object_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEncodedObjectAsID_get_object_id #-}

instance Method "get_object_id" GodotEncodedObjectAsID (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEncodedObjectAsID_get_object_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotJSONParseResult = GodotJSONParseResult GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotJSONParseResult where
        type BaseClass GodotJSONParseResult = GodotReference
        super = coerce
bindJSONParseResult_get_error
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "get_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_get_error #-}

instance Method "get_error" GodotJSONParseResult (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_get_error (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJSONParseResult_get_error_string
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "get_error_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_get_error_string #-}

instance Method "get_error_string" GodotJSONParseResult
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_get_error_string
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJSONParseResult_get_error_line
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "get_error_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_get_error_line #-}

instance Method "get_error_line" GodotJSONParseResult (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_get_error_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJSONParseResult_get_result
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "get_result" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_get_result #-}

instance Method "get_result" GodotJSONParseResult (IO GodotVariant)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_get_result (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJSONParseResult_set_error
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "set_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_set_error #-}

instance Method "set_error" GodotJSONParseResult (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_set_error (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJSONParseResult_set_error_string
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "set_error_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_set_error_string #-}

instance Method "set_error_string" GodotJSONParseResult
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_set_error_string
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJSONParseResult_set_error_line
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "set_error_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_set_error_line #-}

instance Method "set_error_line" GodotJSONParseResult
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_set_error_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJSONParseResult_set_result
  = unsafePerformIO $
      withCString "JSONParseResult" $
        \ clsNamePtr ->
          withCString "set_result" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJSONParseResult_set_result #-}

instance Method "set_result" GodotJSONParseResult
           (GodotVariant -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJSONParseResult_set_result (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotIP_Unix = GodotIP_Unix GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotIP_Unix where
        type BaseClass GodotIP_Unix = GodotIP
        super = coerce

newtype Godot_Geometry = Godot_Geometry GodotObject
                           deriving newtype AsVariant

instance HasBaseClass Godot_Geometry where
        type BaseClass Godot_Geometry = GodotObject
        super = coerce
bind_Geometry_build_box_planes
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "build_box_planes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_build_box_planes #-}

instance Method "build_box_planes" Godot_Geometry
           (GodotVector3 -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_build_box_planes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_build_cylinder_planes
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "build_cylinder_planes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_build_cylinder_planes #-}

instance Method "build_cylinder_planes" Godot_Geometry
           (Float -> Float -> Int -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_build_cylinder_planes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_build_capsule_planes
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "build_capsule_planes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_build_capsule_planes #-}

instance Method "build_capsule_planes" Godot_Geometry
           (Float -> Float -> Int -> Int -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_build_capsule_planes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_segment_intersects_circle
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "segment_intersects_circle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_segment_intersects_circle #-}

instance Method "segment_intersects_circle" Godot_Geometry
           (GodotVector2 -> GodotVector2 -> GodotVector2 -> Float -> IO Float)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_segment_intersects_circle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_segment_intersects_segment_2d
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "segment_intersects_segment_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_segment_intersects_segment_2d #-}

instance Method "segment_intersects_segment_2d" Godot_Geometry
           (GodotVector2 ->
              GodotVector2 -> GodotVector2 -> GodotVector2 -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_segment_intersects_segment_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_line_intersects_line_2d
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "line_intersects_line_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_line_intersects_line_2d #-}

instance Method "line_intersects_line_2d" Godot_Geometry
           (GodotVector2 ->
              GodotVector2 -> GodotVector2 -> GodotVector2 -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_line_intersects_line_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_get_closest_points_between_segments_2d
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "get_closest_points_between_segments_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_get_closest_points_between_segments_2d
             #-}

instance Method "get_closest_points_between_segments_2d"
           Godot_Geometry
           (GodotVector2 ->
              GodotVector2 ->
                GodotVector2 -> GodotVector2 -> IO GodotPoolVector2Array)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_Geometry_get_closest_points_between_segments_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_get_closest_points_between_segments
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "get_closest_points_between_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_get_closest_points_between_segments #-}

instance Method "get_closest_points_between_segments"
           Godot_Geometry
           (GodotVector3 ->
              GodotVector3 ->
                GodotVector3 -> GodotVector3 -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_Geometry_get_closest_points_between_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_get_closest_point_to_segment_2d
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "get_closest_point_to_segment_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_get_closest_point_to_segment_2d #-}

instance Method "get_closest_point_to_segment_2d" Godot_Geometry
           (GodotVector2 -> GodotVector2 -> GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_Geometry_get_closest_point_to_segment_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_get_closest_point_to_segment
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "get_closest_point_to_segment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_get_closest_point_to_segment #-}

instance Method "get_closest_point_to_segment" Godot_Geometry
           (GodotVector3 -> GodotVector3 -> GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_get_closest_point_to_segment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_get_closest_point_to_segment_uncapped_2d
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "get_closest_point_to_segment_uncapped_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_get_closest_point_to_segment_uncapped_2d
             #-}

instance Method "get_closest_point_to_segment_uncapped_2d"
           Godot_Geometry
           (GodotVector2 -> GodotVector2 -> GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_Geometry_get_closest_point_to_segment_uncapped_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_get_closest_point_to_segment_uncapped
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "get_closest_point_to_segment_uncapped" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_get_closest_point_to_segment_uncapped
             #-}

instance Method "get_closest_point_to_segment_uncapped"
           Godot_Geometry
           (GodotVector3 -> GodotVector3 -> GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_Geometry_get_closest_point_to_segment_uncapped
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_get_uv84_normal_bit
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "get_uv84_normal_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_get_uv84_normal_bit #-}

instance Method "get_uv84_normal_bit" Godot_Geometry
           (GodotVector3 -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_get_uv84_normal_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_ray_intersects_triangle
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "ray_intersects_triangle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_ray_intersects_triangle #-}

instance Method "ray_intersects_triangle" Godot_Geometry
           (GodotVector3 ->
              GodotVector3 ->
                GodotVector3 -> GodotVector3 -> GodotVector3 -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_ray_intersects_triangle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_segment_intersects_triangle
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "segment_intersects_triangle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_segment_intersects_triangle #-}

instance Method "segment_intersects_triangle" Godot_Geometry
           (GodotVector3 ->
              GodotVector3 ->
                GodotVector3 -> GodotVector3 -> GodotVector3 -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_segment_intersects_triangle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_segment_intersects_sphere
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "segment_intersects_sphere" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_segment_intersects_sphere #-}

instance Method "segment_intersects_sphere" Godot_Geometry
           (GodotVector3 ->
              GodotVector3 -> GodotVector3 -> Float -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_segment_intersects_sphere
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_segment_intersects_cylinder
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "segment_intersects_cylinder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_segment_intersects_cylinder #-}

instance Method "segment_intersects_cylinder" Godot_Geometry
           (GodotVector3 ->
              GodotVector3 -> Float -> Float -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_segment_intersects_cylinder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_segment_intersects_convex
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "segment_intersects_convex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_segment_intersects_convex #-}

instance Method "segment_intersects_convex" Godot_Geometry
           (GodotVector3 ->
              GodotVector3 -> GodotArray -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_segment_intersects_convex
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_point_is_inside_triangle
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "point_is_inside_triangle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_point_is_inside_triangle #-}

instance Method "point_is_inside_triangle" Godot_Geometry
           (GodotVector2 ->
              GodotVector2 -> GodotVector2 -> GodotVector2 -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_point_is_inside_triangle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_triangulate_polygon
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "triangulate_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_triangulate_polygon #-}

instance Method "triangulate_polygon" Godot_Geometry
           (GodotPoolVector2Array -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_triangulate_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_convex_hull_2d
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "convex_hull_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_convex_hull_2d #-}

instance Method "convex_hull_2d" Godot_Geometry
           (GodotPoolVector2Array -> IO GodotPoolVector2Array)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_convex_hull_2d (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_clip_polygon
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "clip_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_clip_polygon #-}

instance Method "clip_polygon" Godot_Geometry
           (GodotPoolVector3Array -> GodotPlane -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_clip_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Geometry_make_atlas
  = unsafePerformIO $
      withCString "_Geometry" $
        \ clsNamePtr ->
          withCString "make_atlas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Geometry_make_atlas #-}

instance Method "make_atlas" Godot_Geometry
           (GodotPoolVector2Array -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Geometry_make_atlas (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_ResourceLoader = Godot_ResourceLoader GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass Godot_ResourceLoader where
        type BaseClass Godot_ResourceLoader = GodotObject
        super = coerce
bind_ResourceLoader_load_interactive
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "load_interactive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_load_interactive #-}

instance Method "load_interactive" Godot_ResourceLoader
           (GodotString -> GodotString -> IO GodotResourceInteractiveLoader)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceLoader_load_interactive
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceLoader_load
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "load" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_load #-}

instance Method "load" Godot_ResourceLoader
           (GodotString -> GodotString -> Bool -> IO GodotResource)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceLoader_load (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceLoader_get_recognized_extensions_for_type
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "get_recognized_extensions_for_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_get_recognized_extensions_for_type
             #-}

instance Method "get_recognized_extensions_for_type"
           Godot_ResourceLoader
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_ResourceLoader_get_recognized_extensions_for_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceLoader_set_abort_on_missing_resources
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "set_abort_on_missing_resources" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_set_abort_on_missing_resources #-}

instance Method "set_abort_on_missing_resources"
           Godot_ResourceLoader
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_ResourceLoader_set_abort_on_missing_resources
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceLoader_get_dependencies
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "get_dependencies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_get_dependencies #-}

instance Method "get_dependencies" Godot_ResourceLoader
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceLoader_get_dependencies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceLoader_has_cached
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "has_cached" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_has_cached #-}

instance Method "has_cached" Godot_ResourceLoader
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceLoader_has_cached (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceLoader_exists
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "exists" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_exists #-}

instance Method "exists" Godot_ResourceLoader
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceLoader_exists (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceLoader_has
  = unsafePerformIO $
      withCString "_ResourceLoader" $
        \ clsNamePtr ->
          withCString "has" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceLoader_has #-}

instance Method "has" Godot_ResourceLoader (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceLoader_has (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_ResourceSaver = Godot_ResourceSaver GodotObject
                                deriving newtype AsVariant

instance HasBaseClass Godot_ResourceSaver where
        type BaseClass Godot_ResourceSaver = GodotObject
        super = coerce
bind_ResourceSaver_save
  = unsafePerformIO $
      withCString "_ResourceSaver" $
        \ clsNamePtr ->
          withCString "save" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceSaver_save #-}

instance Method "save" Godot_ResourceSaver
           (GodotString -> GodotResource -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceSaver_save (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ResourceSaver_get_recognized_extensions
  = unsafePerformIO $
      withCString "_ResourceSaver" $
        \ clsNamePtr ->
          withCString "get_recognized_extensions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ResourceSaver_get_recognized_extensions #-}

instance Method "get_recognized_extensions" Godot_ResourceSaver
           (GodotResource -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ResourceSaver_get_recognized_extensions
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_OS = Godot_OS GodotObject
                     deriving newtype AsVariant

instance HasBaseClass Godot_OS where
        type BaseClass Godot_OS = GodotObject
        super = coerce
bind_OS_set_clipboard
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_clipboard" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_clipboard #-}

instance Method "set_clipboard" Godot_OS (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_clipboard (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_clipboard
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_clipboard" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_clipboard #-}

instance Method "get_clipboard" Godot_OS (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_clipboard (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_video_driver_count
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_video_driver_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_video_driver_count #-}

instance Method "get_video_driver_count" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_video_driver_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_video_driver_name
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_video_driver_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_video_driver_name #-}

instance Method "get_video_driver_name" Godot_OS
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_video_driver_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_audio_driver_count
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_audio_driver_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_audio_driver_count #-}

instance Method "get_audio_driver_count" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_audio_driver_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_audio_driver_name
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_audio_driver_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_audio_driver_name #-}

instance Method "get_audio_driver_name" Godot_OS
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_audio_driver_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_connected_midi_inputs
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_connected_midi_inputs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_connected_midi_inputs #-}

instance Method "get_connected_midi_inputs" Godot_OS
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_connected_midi_inputs
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_open_midi_inputs
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "open_midi_inputs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_open_midi_inputs #-}

instance Method "open_midi_inputs" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_open_midi_inputs (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_close_midi_inputs
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "close_midi_inputs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_close_midi_inputs #-}

instance Method "close_midi_inputs" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_close_midi_inputs (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_screen_count
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_screen_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_screen_count #-}

instance Method "get_screen_count" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_screen_count (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_current_screen
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_current_screen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_current_screen #-}

instance Method "get_current_screen" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_current_screen (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_current_screen
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_current_screen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_current_screen #-}

instance Method "set_current_screen" Godot_OS (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_current_screen (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_screen_position
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_screen_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_screen_position #-}

instance Method "get_screen_position" Godot_OS
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_screen_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_screen_size
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_screen_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_screen_size #-}

instance Method "get_screen_size" Godot_OS (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_screen_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_screen_dpi
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_screen_dpi" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_screen_dpi #-}

instance Method "get_screen_dpi" Godot_OS (Int -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_screen_dpi (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_window_position
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_window_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_window_position #-}

instance Method "get_window_position" Godot_OS (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_window_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_position
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_position #-}

instance Method "set_window_position" Godot_OS
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_window_size
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_window_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_window_size #-}

instance Method "get_window_size" Godot_OS (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_window_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_size
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_size #-}

instance Method "set_window_size" Godot_OS (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_window_safe_area
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_window_safe_area" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_window_safe_area #-}

instance Method "get_window_safe_area" Godot_OS (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_window_safe_area (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_fullscreen
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_fullscreen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_fullscreen #-}

instance Method "set_window_fullscreen" Godot_OS (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_fullscreen (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_window_fullscreen
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_window_fullscreen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_window_fullscreen #-}

instance Method "is_window_fullscreen" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_window_fullscreen (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_resizable
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_resizable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_resizable #-}

instance Method "set_window_resizable" Godot_OS (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_resizable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_window_resizable
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_window_resizable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_window_resizable #-}

instance Method "is_window_resizable" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_window_resizable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_minimized
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_minimized" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_minimized #-}

instance Method "set_window_minimized" Godot_OS (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_minimized (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_window_minimized
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_window_minimized" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_window_minimized #-}

instance Method "is_window_minimized" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_window_minimized (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_maximized
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_maximized" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_maximized #-}

instance Method "set_window_maximized" Godot_OS (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_maximized (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_window_maximized
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_window_maximized" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_window_maximized #-}

instance Method "is_window_maximized" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_window_maximized (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_always_on_top
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_always_on_top" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_always_on_top #-}

instance Method "set_window_always_on_top" Godot_OS (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_always_on_top
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_window_always_on_top
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_window_always_on_top" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_window_always_on_top #-}

instance Method "is_window_always_on_top" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_window_always_on_top (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_request_attention
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "request_attention" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_request_attention #-}

instance Method "request_attention" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_request_attention (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_real_window_size
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_real_window_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_real_window_size #-}

instance Method "get_real_window_size" Godot_OS (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_real_window_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_center_window
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "center_window" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_center_window #-}

instance Method "center_window" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_center_window (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_borderless_window
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_borderless_window" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_borderless_window #-}

instance Method "set_borderless_window" Godot_OS (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_borderless_window (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_borderless_window
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_borderless_window" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_borderless_window #-}

instance Method "get_borderless_window" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_borderless_window (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_window_per_pixel_transparency_enabled
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_window_per_pixel_transparency_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_window_per_pixel_transparency_enabled #-}

instance Method "get_window_per_pixel_transparency_enabled"
           Godot_OS
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_OS_get_window_per_pixel_transparency_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_per_pixel_transparency_enabled
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_per_pixel_transparency_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_per_pixel_transparency_enabled #-}

instance Method "set_window_per_pixel_transparency_enabled"
           Godot_OS
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bind_OS_set_window_per_pixel_transparency_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_ime_position
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_ime_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_ime_position #-}

instance Method "set_ime_position" Godot_OS (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_ime_position (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_screen_orientation
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_screen_orientation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_screen_orientation #-}

instance Method "set_screen_orientation" Godot_OS (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_screen_orientation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_screen_orientation
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_screen_orientation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_screen_orientation #-}

instance Method "get_screen_orientation" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_screen_orientation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_keep_screen_on
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_keep_screen_on" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_keep_screen_on #-}

instance Method "set_keep_screen_on" Godot_OS (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_keep_screen_on (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_keep_screen_on
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_keep_screen_on" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_keep_screen_on #-}

instance Method "is_keep_screen_on" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_keep_screen_on (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_has_touchscreen_ui_hint
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "has_touchscreen_ui_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_has_touchscreen_ui_hint #-}

instance Method "has_touchscreen_ui_hint" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_has_touchscreen_ui_hint (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_window_title
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_window_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_window_title #-}

instance Method "set_window_title" Godot_OS (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_window_title (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_low_processor_usage_mode
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_low_processor_usage_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_low_processor_usage_mode #-}

instance Method "set_low_processor_usage_mode" Godot_OS
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_low_processor_usage_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_in_low_processor_usage_mode
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_in_low_processor_usage_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_in_low_processor_usage_mode #-}

instance Method "is_in_low_processor_usage_mode" Godot_OS (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_in_low_processor_usage_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_processor_count
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_processor_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_processor_count #-}

instance Method "get_processor_count" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_processor_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_executable_path
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_executable_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_executable_path #-}

instance Method "get_executable_path" Godot_OS (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_executable_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_execute
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "execute" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_execute #-}

instance Method "execute" Godot_OS
           (GodotString ->
              GodotPoolStringArray -> Bool -> GodotArray -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_execute (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_kill
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "kill" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_kill #-}

instance Method "kill" Godot_OS (Int -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_kill (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_shell_open
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "shell_open" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_shell_open #-}

instance Method "shell_open" Godot_OS (GodotString -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_shell_open (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_process_id
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_process_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_process_id #-}

instance Method "get_process_id" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_process_id (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_environment
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_environment #-}

instance Method "get_environment" Godot_OS
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_environment (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_has_environment
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "has_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_has_environment #-}

instance Method "has_environment" Godot_OS (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_has_environment (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_name
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_name #-}

instance Method "get_name" Godot_OS (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_name (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_cmdline_args
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_cmdline_args" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_cmdline_args #-}

instance Method "get_cmdline_args" Godot_OS
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_cmdline_args (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_datetime
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_datetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_datetime #-}

instance Method "get_datetime" Godot_OS
           (Bool -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_datetime (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_date
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_date" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_date #-}

instance Method "get_date" Godot_OS (Bool -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_date (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_time
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_time #-}

instance Method "get_time" Godot_OS (Bool -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_time (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_time_zone_info
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_time_zone_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_time_zone_info #-}

instance Method "get_time_zone_info" Godot_OS (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_time_zone_info (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_unix_time
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_unix_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_unix_time #-}

instance Method "get_unix_time" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_unix_time (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_datetime_from_unix_time
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_datetime_from_unix_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_datetime_from_unix_time #-}

instance Method "get_datetime_from_unix_time" Godot_OS
           (Int -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_datetime_from_unix_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_unix_time_from_datetime
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_unix_time_from_datetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_unix_time_from_datetime #-}

instance Method "get_unix_time_from_datetime" Godot_OS
           (GodotDictionary -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_unix_time_from_datetime
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_system_time_secs
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_system_time_secs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_system_time_secs #-}

instance Method "get_system_time_secs" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_system_time_secs (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_icon
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_icon #-}

instance Method "set_icon" Godot_OS (GodotImage -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_icon (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_exit_code
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_exit_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_exit_code #-}

instance Method "get_exit_code" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_exit_code (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_exit_code
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_exit_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_exit_code #-}

instance Method "set_exit_code" Godot_OS (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_exit_code (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_delay_usec
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "delay_usec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_delay_usec #-}

instance Method "delay_usec" Godot_OS (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_delay_usec (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_delay_msec
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "delay_msec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_delay_msec #-}

instance Method "delay_msec" Godot_OS (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_delay_msec (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_ticks_msec
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_ticks_msec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_ticks_msec #-}

instance Method "get_ticks_msec" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_ticks_msec (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_ticks_usec
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_ticks_usec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_ticks_usec #-}

instance Method "get_ticks_usec" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_ticks_usec (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_splash_tick_msec
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_splash_tick_msec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_splash_tick_msec #-}

instance Method "get_splash_tick_msec" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_splash_tick_msec (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_locale
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_locale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_locale #-}

instance Method "get_locale" Godot_OS (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_locale (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_latin_keyboard_variant
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_latin_keyboard_variant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_latin_keyboard_variant #-}

instance Method "get_latin_keyboard_variant" Godot_OS
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_latin_keyboard_variant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_model_name
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_model_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_model_name #-}

instance Method "get_model_name" Godot_OS (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_model_name (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_can_draw
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "can_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_can_draw #-}

instance Method "can_draw" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_can_draw (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_userfs_persistent
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_userfs_persistent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_userfs_persistent #-}

instance Method "is_userfs_persistent" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_userfs_persistent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_stdout_verbose
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_stdout_verbose" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_stdout_verbose #-}

instance Method "is_stdout_verbose" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_stdout_verbose (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_can_use_threads
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "can_use_threads" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_can_use_threads #-}

instance Method "can_use_threads" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_can_use_threads (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_debug_build
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_debug_build" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_debug_build #-}

instance Method "is_debug_build" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_debug_build (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_dump_memory_to_file
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "dump_memory_to_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_dump_memory_to_file #-}

instance Method "dump_memory_to_file" Godot_OS
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_dump_memory_to_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_dump_resources_to_file
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "dump_resources_to_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_dump_resources_to_file #-}

instance Method "dump_resources_to_file" Godot_OS
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_dump_resources_to_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_has_virtual_keyboard
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "has_virtual_keyboard" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_has_virtual_keyboard #-}

instance Method "has_virtual_keyboard" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_has_virtual_keyboard (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_show_virtual_keyboard
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "show_virtual_keyboard" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_show_virtual_keyboard #-}

instance Method "show_virtual_keyboard" Godot_OS
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_show_virtual_keyboard (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_hide_virtual_keyboard
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "hide_virtual_keyboard" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_hide_virtual_keyboard #-}

instance Method "hide_virtual_keyboard" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_hide_virtual_keyboard (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_virtual_keyboard_height
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_virtual_keyboard_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_virtual_keyboard_height #-}

instance Method "get_virtual_keyboard_height" Godot_OS (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_virtual_keyboard_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_print_resources_in_use
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "print_resources_in_use" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_print_resources_in_use #-}

instance Method "print_resources_in_use" Godot_OS (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_print_resources_in_use (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_print_all_resources
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "print_all_resources" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_print_all_resources #-}

instance Method "print_all_resources" Godot_OS
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_print_all_resources (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_static_memory_usage
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_static_memory_usage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_static_memory_usage #-}

instance Method "get_static_memory_usage" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_static_memory_usage (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_static_memory_peak_usage
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_static_memory_peak_usage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_static_memory_peak_usage #-}

instance Method "get_static_memory_peak_usage" Godot_OS (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_static_memory_peak_usage
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_dynamic_memory_usage
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_dynamic_memory_usage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_dynamic_memory_usage #-}

instance Method "get_dynamic_memory_usage" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_dynamic_memory_usage
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_user_data_dir
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_user_data_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_user_data_dir #-}

instance Method "get_user_data_dir" Godot_OS (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_user_data_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_system_dir
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_system_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_system_dir #-}

instance Method "get_system_dir" Godot_OS (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_system_dir (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_unique_id
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_unique_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_unique_id #-}

instance Method "get_unique_id" Godot_OS (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_unique_id (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_ok_left_and_cancel_right
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_ok_left_and_cancel_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_ok_left_and_cancel_right #-}

instance Method "is_ok_left_and_cancel_right" Godot_OS (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_ok_left_and_cancel_right
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_print_all_textures_by_size
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "print_all_textures_by_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_print_all_textures_by_size #-}

instance Method "print_all_textures_by_size" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_print_all_textures_by_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_print_resources_by_type
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "print_resources_by_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_print_resources_by_type #-}

instance Method "print_resources_by_type" Godot_OS
           (GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_print_resources_by_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_native_video_play
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "native_video_play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_native_video_play #-}

instance Method "native_video_play" Godot_OS
           (GodotString -> Float -> GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_native_video_play (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_native_video_is_playing
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "native_video_is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_native_video_is_playing #-}

instance Method "native_video_is_playing" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_native_video_is_playing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_native_video_stop
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "native_video_stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_native_video_stop #-}

instance Method "native_video_stop" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_native_video_stop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_native_video_pause
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "native_video_pause" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_native_video_pause #-}

instance Method "native_video_pause" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_native_video_pause (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_native_video_unpause
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "native_video_unpause" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_native_video_unpause #-}

instance Method "native_video_unpause" Godot_OS (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_native_video_unpause (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_scancode_string
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_scancode_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_scancode_string #-}

instance Method "get_scancode_string" Godot_OS
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_scancode_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_scancode_unicode
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_scancode_unicode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_scancode_unicode #-}

instance Method "is_scancode_unicode" Godot_OS (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_scancode_unicode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_find_scancode_from_string
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "find_scancode_from_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_find_scancode_from_string #-}

instance Method "find_scancode_from_string" Godot_OS
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_find_scancode_from_string
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_use_file_access_save_and_swap
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_use_file_access_save_and_swap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_use_file_access_save_and_swap #-}

instance Method "set_use_file_access_save_and_swap" Godot_OS
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_use_file_access_save_and_swap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_alert
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "alert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_alert #-}

instance Method "alert" Godot_OS
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_alert (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_thread_name
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_thread_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_thread_name #-}

instance Method "set_thread_name" Godot_OS (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_thread_name (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_set_use_vsync
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "set_use_vsync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_set_use_vsync #-}

instance Method "set_use_vsync" Godot_OS (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_set_use_vsync (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_is_vsync_enabled
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "is_vsync_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_is_vsync_enabled #-}

instance Method "is_vsync_enabled" Godot_OS (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_is_vsync_enabled (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_has_feature
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "has_feature" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_has_feature #-}

instance Method "has_feature" Godot_OS (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_has_feature (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_power_state
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_power_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_power_state #-}

instance Method "get_power_state" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_power_state (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_power_seconds_left
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_power_seconds_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_power_seconds_left #-}

instance Method "get_power_seconds_left" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_power_seconds_left (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_OS_get_power_percent_left
  = unsafePerformIO $
      withCString "_OS" $
        \ clsNamePtr ->
          withCString "get_power_percent_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_OS_get_power_percent_left #-}

instance Method "get_power_percent_left" Godot_OS (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_OS_get_power_percent_left (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_Engine = Godot_Engine GodotObject
                         deriving newtype AsVariant

instance HasBaseClass Godot_Engine where
        type BaseClass Godot_Engine = GodotObject
        super = coerce
bind_Engine_set_iterations_per_second
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "set_iterations_per_second" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_set_iterations_per_second #-}

instance Method "set_iterations_per_second" Godot_Engine
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_set_iterations_per_second
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_iterations_per_second
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_iterations_per_second" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_iterations_per_second #-}

instance Method "get_iterations_per_second" Godot_Engine (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_iterations_per_second
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_set_physics_jitter_fix
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "set_physics_jitter_fix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_set_physics_jitter_fix #-}

instance Method "set_physics_jitter_fix" Godot_Engine
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_set_physics_jitter_fix
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_physics_jitter_fix
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_physics_jitter_fix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_physics_jitter_fix #-}

instance Method "get_physics_jitter_fix" Godot_Engine (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_physics_jitter_fix
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_set_target_fps
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "set_target_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_set_target_fps #-}

instance Method "set_target_fps" Godot_Engine (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_set_target_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_target_fps
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_target_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_target_fps #-}

instance Method "get_target_fps" Godot_Engine (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_target_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_set_time_scale
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "set_time_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_set_time_scale #-}

instance Method "set_time_scale" Godot_Engine (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_set_time_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_time_scale
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_time_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_time_scale #-}

instance Method "get_time_scale" Godot_Engine (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_time_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_frames_drawn
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_frames_drawn" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_frames_drawn #-}

instance Method "get_frames_drawn" Godot_Engine (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_frames_drawn (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_frames_per_second
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_frames_per_second" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_frames_per_second #-}

instance Method "get_frames_per_second" Godot_Engine (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_frames_per_second
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_main_loop
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_main_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_main_loop #-}

instance Method "get_main_loop" Godot_Engine (IO GodotMainLoop)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_main_loop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_version_info
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_version_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_version_info #-}

instance Method "get_version_info" Godot_Engine
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_version_info (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_author_info
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_author_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_author_info #-}

instance Method "get_author_info" Godot_Engine (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_author_info (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_copyright_info
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_copyright_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_copyright_info #-}

instance Method "get_copyright_info" Godot_Engine (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_copyright_info (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_donor_info
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_donor_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_donor_info #-}

instance Method "get_donor_info" Godot_Engine (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_donor_info (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_license_info
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_license_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_license_info #-}

instance Method "get_license_info" Godot_Engine
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_license_info (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_license_text
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_license_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_license_text #-}

instance Method "get_license_text" Godot_Engine (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_license_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_is_in_physics_frame
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "is_in_physics_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_is_in_physics_frame #-}

instance Method "is_in_physics_frame" Godot_Engine (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_is_in_physics_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_has_singleton
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "has_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_has_singleton #-}

instance Method "has_singleton" Godot_Engine
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_has_singleton (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_get_singleton
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "get_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_get_singleton #-}

instance Method "get_singleton" Godot_Engine
           (GodotString -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_get_singleton (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_set_editor_hint
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "set_editor_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_set_editor_hint #-}

instance Method "set_editor_hint" Godot_Engine (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_set_editor_hint (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Engine_is_editor_hint
  = unsafePerformIO $
      withCString "_Engine" $
        \ clsNamePtr ->
          withCString "is_editor_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Engine_is_editor_hint #-}

instance Method "is_editor_hint" Godot_Engine (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Engine_is_editor_hint (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_ClassDB = Godot_ClassDB GodotObject
                          deriving newtype AsVariant

instance HasBaseClass Godot_ClassDB where
        type BaseClass Godot_ClassDB = GodotObject
        super = coerce
bind_ClassDB_get_class_list
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "get_class_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_get_class_list #-}

instance Method "get_class_list" Godot_ClassDB
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_get_class_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_get_inheriters_from_class
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "get_inheriters_from_class" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_get_inheriters_from_class #-}

instance Method "get_inheriters_from_class" Godot_ClassDB
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_get_inheriters_from_class
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_get_parent_class
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "get_parent_class" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_get_parent_class #-}

instance Method "get_parent_class" Godot_ClassDB
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_get_parent_class (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_exists
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_exists" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_exists #-}

instance Method "class_exists" Godot_ClassDB
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_exists (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_is_parent_class
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "is_parent_class" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_is_parent_class #-}

instance Method "is_parent_class" Godot_ClassDB
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_is_parent_class (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_can_instance
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "can_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_can_instance #-}

instance Method "can_instance" Godot_ClassDB
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_can_instance (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_instance
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_instance #-}

instance Method "instance" Godot_ClassDB
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_instance (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_has_signal
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_has_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_has_signal #-}

instance Method "class_has_signal" Godot_ClassDB
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_has_signal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_signal
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_signal #-}

instance Method "class_get_signal" Godot_ClassDB
           (GodotString -> GodotString -> IO GodotDictionary)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_signal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_signal_list
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_signal_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_signal_list #-}

instance Method "class_get_signal_list" Godot_ClassDB
           (GodotString -> Bool -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_signal_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_property_list
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_property_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_property_list #-}

instance Method "class_get_property_list" Godot_ClassDB
           (GodotString -> Bool -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_property_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_property
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_property #-}

instance Method "class_get_property" Godot_ClassDB
           (GodotObject -> GodotString -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_property (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_set_property
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_set_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_set_property #-}

instance Method "class_set_property" Godot_ClassDB
           (GodotObject -> GodotString -> GodotVariant -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_set_property (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_has_method
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_has_method" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_has_method #-}

instance Method "class_has_method" Godot_ClassDB
           (GodotString -> GodotString -> Bool -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_has_method (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_method_list
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_method_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_method_list #-}

instance Method "class_get_method_list" Godot_ClassDB
           (GodotString -> Bool -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_method_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_integer_constant_list
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_integer_constant_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_integer_constant_list #-}

instance Method "class_get_integer_constant_list" Godot_ClassDB
           (GodotString -> Bool -> IO GodotPoolStringArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_integer_constant_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_has_integer_constant
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_has_integer_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_has_integer_constant #-}

instance Method "class_has_integer_constant" Godot_ClassDB
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_has_integer_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_integer_constant
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_integer_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_integer_constant #-}

instance Method "class_get_integer_constant" Godot_ClassDB
           (GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_integer_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_class_get_category
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "class_get_category" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_class_get_category #-}

instance Method "class_get_category" Godot_ClassDB
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_class_get_category (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_ClassDB_is_class_enabled
  = unsafePerformIO $
      withCString "_ClassDB" $
        \ clsNamePtr ->
          withCString "is_class_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_ClassDB_is_class_enabled #-}

instance Method "is_class_enabled" Godot_ClassDB
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_ClassDB_is_class_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_Marshalls = Godot_Marshalls GodotObject
                            deriving newtype AsVariant

instance HasBaseClass Godot_Marshalls where
        type BaseClass Godot_Marshalls = GodotReference
        super = coerce
bind_Marshalls_variant_to_base64
  = unsafePerformIO $
      withCString "_Marshalls" $
        \ clsNamePtr ->
          withCString "variant_to_base64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Marshalls_variant_to_base64 #-}

instance Method "variant_to_base64" Godot_Marshalls
           (GodotVariant -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Marshalls_variant_to_base64
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Marshalls_base64_to_variant
  = unsafePerformIO $
      withCString "_Marshalls" $
        \ clsNamePtr ->
          withCString "base64_to_variant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Marshalls_base64_to_variant #-}

instance Method "base64_to_variant" Godot_Marshalls
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Marshalls_base64_to_variant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Marshalls_raw_to_base64
  = unsafePerformIO $
      withCString "_Marshalls" $
        \ clsNamePtr ->
          withCString "raw_to_base64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Marshalls_raw_to_base64 #-}

instance Method "raw_to_base64" Godot_Marshalls
           (GodotPoolByteArray -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Marshalls_raw_to_base64 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Marshalls_base64_to_raw
  = unsafePerformIO $
      withCString "_Marshalls" $
        \ clsNamePtr ->
          withCString "base64_to_raw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Marshalls_base64_to_raw #-}

instance Method "base64_to_raw" Godot_Marshalls
           (GodotString -> IO GodotPoolByteArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Marshalls_base64_to_raw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Marshalls_utf8_to_base64
  = unsafePerformIO $
      withCString "_Marshalls" $
        \ clsNamePtr ->
          withCString "utf8_to_base64" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Marshalls_utf8_to_base64 #-}

instance Method "utf8_to_base64" Godot_Marshalls
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Marshalls_utf8_to_base64 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_Marshalls_base64_to_utf8
  = unsafePerformIO $
      withCString "_Marshalls" $
        \ clsNamePtr ->
          withCString "base64_to_utf8" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_Marshalls_base64_to_utf8 #-}

instance Method "base64_to_utf8" Godot_Marshalls
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_Marshalls_base64_to_utf8 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_JSON = Godot_JSON GodotObject
                       deriving newtype AsVariant

instance HasBaseClass Godot_JSON where
        type BaseClass Godot_JSON = GodotObject
        super = coerce
bind_JSON_print
  = unsafePerformIO $
      withCString "_JSON" $
        \ clsNamePtr ->
          withCString "print" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_JSON_print #-}

instance Method "print" Godot_JSON
           (GodotVariant -> GodotString -> Bool -> IO GodotString)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_JSON_print (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_JSON_parse
  = unsafePerformIO $
      withCString "_JSON" $
        \ clsNamePtr ->
          withCString "parse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_JSON_parse #-}

instance Method "parse" Godot_JSON
           (GodotString -> IO GodotJSONParseResult)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_JSON_parse (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotProjectSettings = GodotProjectSettings GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotProjectSettings where
        type BaseClass GodotProjectSettings = GodotObject
        super = coerce
bindProjectSettings_has_setting
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "has_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_has_setting #-}

instance Method "has_setting" GodotProjectSettings
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_has_setting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_set_setting
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "set_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_set_setting #-}

instance Method "set_setting" GodotProjectSettings
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_set_setting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_get_setting
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "get_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_get_setting #-}

instance Method "get_setting" GodotProjectSettings
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_get_setting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_set_order
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "set_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_set_order #-}

instance Method "set_order" GodotProjectSettings
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_set_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_get_order
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "get_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_get_order #-}

instance Method "get_order" GodotProjectSettings
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_get_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_set_initial_value
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "set_initial_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_set_initial_value #-}

instance Method "set_initial_value" GodotProjectSettings
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_set_initial_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_add_property_info
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "add_property_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_add_property_info #-}

instance Method "add_property_info" GodotProjectSettings
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_add_property_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_clear
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_clear #-}

instance Method "clear" GodotProjectSettings (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_clear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_localize_path
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "localize_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_localize_path #-}

instance Method "localize_path" GodotProjectSettings
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_localize_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_globalize_path
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "globalize_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_globalize_path #-}

instance Method "globalize_path" GodotProjectSettings
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_globalize_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_save
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "save" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_save #-}

instance Method "save" GodotProjectSettings (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_save (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_load_resource_pack
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "load_resource_pack" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_load_resource_pack #-}

instance Method "load_resource_pack" GodotProjectSettings
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_load_resource_pack
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_property_can_revert
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "property_can_revert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_property_can_revert #-}

instance Method "property_can_revert" GodotProjectSettings
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_property_can_revert
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_property_get_revert
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "property_get_revert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_property_get_revert #-}

instance Method "property_get_revert" GodotProjectSettings
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_property_get_revert
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProjectSettings_save_custom
  = unsafePerformIO $
      withCString "ProjectSettings" $
        \ clsNamePtr ->
          withCString "save_custom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProjectSettings_save_custom #-}

instance Method "save_custom" GodotProjectSettings
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProjectSettings_save_custom (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputMap = GodotInputMap GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotInputMap where
        type BaseClass GodotInputMap = GodotObject
        super = coerce
bindInputMap_has_action
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "has_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_has_action #-}

instance Method "has_action" GodotInputMap (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_has_action (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_get_actions
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "get_actions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_get_actions #-}

instance Method "get_actions" GodotInputMap (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_get_actions (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_add_action
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "add_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_add_action #-}

instance Method "add_action" GodotInputMap
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_add_action (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_erase_action
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "erase_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_erase_action #-}

instance Method "erase_action" GodotInputMap (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_erase_action (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_action_set_deadzone
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "action_set_deadzone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_action_set_deadzone #-}

instance Method "action_set_deadzone" GodotInputMap
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_action_set_deadzone
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_action_add_event
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "action_add_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_action_add_event #-}

instance Method "action_add_event" GodotInputMap
           (GodotString -> GodotInputEvent -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_action_add_event (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_action_has_event
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "action_has_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_action_has_event #-}

instance Method "action_has_event" GodotInputMap
           (GodotString -> GodotInputEvent -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_action_has_event (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_action_erase_event
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "action_erase_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_action_erase_event #-}

instance Method "action_erase_event" GodotInputMap
           (GodotString -> GodotInputEvent -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_action_erase_event (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_action_erase_events
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "action_erase_events" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_action_erase_events #-}

instance Method "action_erase_events" GodotInputMap
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_action_erase_events
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_get_action_list
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "get_action_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_get_action_list #-}

instance Method "get_action_list" GodotInputMap
           (GodotString -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_get_action_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_event_is_action
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "event_is_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_event_is_action #-}

instance Method "event_is_action" GodotInputMap
           (GodotInputEvent -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_event_is_action (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInputMap_load_from_globals
  = unsafePerformIO $
      withCString "InputMap" $
        \ clsNamePtr ->
          withCString "load_from_globals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInputMap_load_from_globals #-}

instance Method "load_from_globals" GodotInputMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInputMap_load_from_globals (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTranslationServer = GodotTranslationServer GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotTranslationServer where
        type BaseClass GodotTranslationServer = GodotObject
        super = coerce
bindTranslationServer_set_locale
  = unsafePerformIO $
      withCString "TranslationServer" $
        \ clsNamePtr ->
          withCString "set_locale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslationServer_set_locale #-}

instance Method "set_locale" GodotTranslationServer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslationServer_set_locale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslationServer_get_locale
  = unsafePerformIO $
      withCString "TranslationServer" $
        \ clsNamePtr ->
          withCString "get_locale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslationServer_get_locale #-}

instance Method "get_locale" GodotTranslationServer
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslationServer_get_locale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslationServer_get_locale_name
  = unsafePerformIO $
      withCString "TranslationServer" $
        \ clsNamePtr ->
          withCString "get_locale_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslationServer_get_locale_name #-}

instance Method "get_locale_name" GodotTranslationServer
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslationServer_get_locale_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslationServer_translate
  = unsafePerformIO $
      withCString "TranslationServer" $
        \ clsNamePtr ->
          withCString "translate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslationServer_translate #-}

instance Method "translate" GodotTranslationServer
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslationServer_translate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslationServer_add_translation
  = unsafePerformIO $
      withCString "TranslationServer" $
        \ clsNamePtr ->
          withCString "add_translation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslationServer_add_translation #-}

instance Method "add_translation" GodotTranslationServer
           (GodotTranslation -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslationServer_add_translation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslationServer_remove_translation
  = unsafePerformIO $
      withCString "TranslationServer" $
        \ clsNamePtr ->
          withCString "remove_translation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslationServer_remove_translation #-}

instance Method "remove_translation" GodotTranslationServer
           (GodotTranslation -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslationServer_remove_translation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTranslationServer_clear
  = unsafePerformIO $
      withCString "TranslationServer" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTranslationServer_clear #-}

instance Method "clear" GodotTranslationServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTranslationServer_clear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPerformance = GodotPerformance GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotPerformance where
        type BaseClass GodotPerformance = GodotObject
        super = coerce
bindPerformance_get_monitor
  = unsafePerformIO $
      withCString "Performance" $
        \ clsNamePtr ->
          withCString "get_monitor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPerformance_get_monitor #-}

instance Method "get_monitor" GodotPerformance (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPerformance_get_monitor (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualServer = GodotVisualServer GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotVisualServer where
        type BaseClass GodotVisualServer = GodotObject
        super = coerce
bindVisualServer_force_sync
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "force_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_force_sync #-}

instance Method "force_sync" GodotVisualServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_force_sync (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_force_draw
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "force_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_force_draw #-}

instance Method "force_draw" GodotVisualServer
           (Bool -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_force_draw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_sync
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_sync #-}

instance Method "sync" GodotVisualServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_sync (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_draw
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_draw #-}

instance Method "draw" GodotVisualServer (Bool -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_draw (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_create #-}

instance Method "texture_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_create_from_image
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_create_from_image" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_create_from_image #-}

instance Method "texture_create_from_image" GodotVisualServer
           (GodotImage -> Int -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_create_from_image
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_allocate
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_allocate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_allocate #-}

instance Method "texture_allocate" GodotVisualServer
           (GodotRid -> Int -> Int -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_allocate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_set_data
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_set_data #-}

instance Method "texture_set_data" GodotVisualServer
           (GodotRid -> GodotImage -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_set_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_set_data_partial
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_set_data_partial" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_set_data_partial #-}

instance Method "texture_set_data_partial" GodotVisualServer
           (GodotRid ->
              GodotImage ->
                Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9, toVariant arg10]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_set_data_partial
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_data
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_data #-}

instance Method "texture_get_data" GodotVisualServer
           (GodotRid -> Int -> IO GodotImage)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_set_flags
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_set_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_set_flags #-}

instance Method "texture_set_flags" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_set_flags
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_flags
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_flags #-}

instance Method "texture_get_flags" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_flags
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_format
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_format #-}

instance Method "texture_get_format" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_type
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_type #-}

instance Method "texture_get_type" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_texid
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_texid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_texid #-}

instance Method "texture_get_texid" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_texid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_width
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_width #-}

instance Method "texture_get_width" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_height
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_height #-}

instance Method "texture_get_height" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_depth
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_depth #-}

instance Method "texture_get_depth" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_set_size_override
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_set_size_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_set_size_override #-}

instance Method "texture_set_size_override" GodotVisualServer
           (GodotRid -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_set_size_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_set_path
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_set_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_set_path #-}

instance Method "texture_set_path" GodotVisualServer
           (GodotRid -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_set_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_get_path
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_get_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_get_path #-}

instance Method "texture_get_path" GodotVisualServer
           (GodotRid -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_get_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_set_shrink_all_x2_on_set_data
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_set_shrink_all_x2_on_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_set_shrink_all_x2_on_set_data
             #-}

instance Method "texture_set_shrink_all_x2_on_set_data"
           GodotVisualServer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_texture_set_shrink_all_x2_on_set_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_texture_debug_usage
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "texture_debug_usage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_texture_debug_usage #-}

instance Method "texture_debug_usage" GodotVisualServer
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_texture_debug_usage
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_textures_keep_original
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "textures_keep_original" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_textures_keep_original #-}

instance Method "textures_keep_original" GodotVisualServer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_textures_keep_original
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_sky_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "sky_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_sky_create #-}

instance Method "sky_create" GodotVisualServer (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_sky_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_sky_set_texture
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "sky_set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_sky_set_texture #-}

instance Method "sky_set_texture" GodotVisualServer
           (GodotRid -> GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_sky_set_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_shader_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "shader_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_shader_create #-}

instance Method "shader_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_shader_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_shader_set_code
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "shader_set_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_shader_set_code #-}

instance Method "shader_set_code" GodotVisualServer
           (GodotRid -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_shader_set_code
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_shader_get_code
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "shader_get_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_shader_get_code #-}

instance Method "shader_get_code" GodotVisualServer
           (GodotRid -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_shader_get_code
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_shader_get_param_list
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "shader_get_param_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_shader_get_param_list #-}

instance Method "shader_get_param_list" GodotVisualServer
           (GodotRid -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_shader_get_param_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_shader_set_default_texture_param
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "shader_set_default_texture_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_shader_set_default_texture_param #-}

instance Method "shader_set_default_texture_param"
           GodotVisualServer
           (GodotRid -> GodotString -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_shader_set_default_texture_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_shader_get_default_texture_param
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "shader_get_default_texture_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_shader_get_default_texture_param #-}

instance Method "shader_get_default_texture_param"
           GodotVisualServer
           (GodotRid -> GodotString -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_shader_get_default_texture_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_create #-}

instance Method "material_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_set_shader
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_set_shader" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_set_shader #-}

instance Method "material_set_shader" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_set_shader
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_get_shader
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_get_shader" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_get_shader #-}

instance Method "material_get_shader" GodotVisualServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_get_shader
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_set_param
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_set_param #-}

instance Method "material_set_param" GodotVisualServer
           (GodotRid -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_get_param
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_get_param #-}

instance Method "material_get_param" GodotVisualServer
           (GodotRid -> GodotString -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_get_param_default
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_get_param_default" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_get_param_default #-}

instance Method "material_get_param_default" GodotVisualServer
           (GodotRid -> GodotString -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_get_param_default
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_set_render_priority
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_set_render_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_set_render_priority #-}

instance Method "material_set_render_priority" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_material_set_render_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_set_line_width
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_set_line_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_set_line_width #-}

instance Method "material_set_line_width" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_set_line_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_material_set_next_pass
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "material_set_next_pass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_material_set_next_pass #-}

instance Method "material_set_next_pass" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_material_set_next_pass
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_create #-}

instance Method "mesh_create" GodotVisualServer (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_format_offset
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_format_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_format_offset #-}

instance Method "mesh_surface_get_format_offset" GodotVisualServer
           (Int -> Int -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_surface_get_format_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_format_stride
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_format_stride" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_format_stride #-}

instance Method "mesh_surface_get_format_stride" GodotVisualServer
           (Int -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_surface_get_format_stride
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_add_surface_from_arrays
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_add_surface_from_arrays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_add_surface_from_arrays #-}

instance Method "mesh_add_surface_from_arrays" GodotVisualServer
           (GodotRid -> Int -> GodotArray -> GodotArray -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_add_surface_from_arrays
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_set_blend_shape_count
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_set_blend_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_set_blend_shape_count #-}

instance Method "mesh_set_blend_shape_count" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_set_blend_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_get_blend_shape_count
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_get_blend_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_get_blend_shape_count #-}

instance Method "mesh_get_blend_shape_count" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_get_blend_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_set_blend_shape_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_set_blend_shape_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_set_blend_shape_mode #-}

instance Method "mesh_set_blend_shape_mode" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_set_blend_shape_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_get_blend_shape_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_get_blend_shape_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_get_blend_shape_mode #-}

instance Method "mesh_get_blend_shape_mode" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_get_blend_shape_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_update_region
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_update_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_update_region #-}

instance Method "mesh_surface_update_region" GodotVisualServer
           (GodotRid -> Int -> Int -> GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_update_region
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_set_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_set_material #-}

instance Method "mesh_surface_set_material" GodotVisualServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_set_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_material #-}

instance Method "mesh_surface_get_material" GodotVisualServer
           (GodotRid -> Int -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_get_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_array_len
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_array_len" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_array_len #-}

instance Method "mesh_surface_get_array_len" GodotVisualServer
           (GodotRid -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_get_array_len
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_array_index_len
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_array_index_len" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_array_index_len #-}

instance Method "mesh_surface_get_array_index_len"
           GodotVisualServer
           (GodotRid -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_surface_get_array_index_len
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_array
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_array #-}

instance Method "mesh_surface_get_array" GodotVisualServer
           (GodotRid -> Int -> IO GodotPoolByteArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_get_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_index_array
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_index_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_index_array #-}

instance Method "mesh_surface_get_index_array" GodotVisualServer
           (GodotRid -> Int -> IO GodotPoolByteArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_surface_get_index_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_arrays
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_arrays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_arrays #-}

instance Method "mesh_surface_get_arrays" GodotVisualServer
           (GodotRid -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_get_arrays
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_blend_shape_arrays
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_blend_shape_arrays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_blend_shape_arrays
             #-}

instance Method "mesh_surface_get_blend_shape_arrays"
           GodotVisualServer
           (GodotRid -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_surface_get_blend_shape_arrays
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_format
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_format #-}

instance Method "mesh_surface_get_format" GodotVisualServer
           (GodotRid -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_get_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_primitive_type
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_primitive_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_primitive_type #-}

instance Method "mesh_surface_get_primitive_type" GodotVisualServer
           (GodotRid -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_surface_get_primitive_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_aabb #-}

instance Method "mesh_surface_get_aabb" GodotVisualServer
           (GodotRid -> Int -> IO GodotAabb)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_surface_get_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_surface_get_skeleton_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_surface_get_skeleton_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_surface_get_skeleton_aabb #-}

instance Method "mesh_surface_get_skeleton_aabb" GodotVisualServer
           (GodotRid -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_mesh_surface_get_skeleton_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_remove_surface
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_remove_surface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_remove_surface #-}

instance Method "mesh_remove_surface" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_remove_surface
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_get_surface_count
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_get_surface_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_get_surface_count #-}

instance Method "mesh_get_surface_count" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_get_surface_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_set_custom_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_set_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_set_custom_aabb #-}

instance Method "mesh_set_custom_aabb" GodotVisualServer
           (GodotRid -> GodotAabb -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_set_custom_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_get_custom_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_get_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_get_custom_aabb #-}

instance Method "mesh_get_custom_aabb" GodotVisualServer
           (GodotRid -> IO GodotAabb)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_get_custom_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_mesh_clear
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "mesh_clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_mesh_clear #-}

instance Method "mesh_clear" GodotVisualServer (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_mesh_clear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_allocate
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_allocate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_allocate #-}

instance Method "multimesh_allocate" GodotVisualServer
           (GodotRid -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_multimesh_allocate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_get_instance_count
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_get_instance_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_get_instance_count #-}

instance Method "multimesh_get_instance_count" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_get_instance_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_set_mesh
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_set_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_set_mesh #-}

instance Method "multimesh_set_mesh" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_multimesh_set_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_set_transform #-}

instance Method "multimesh_instance_set_transform"
           GodotVisualServer
           (GodotRid -> Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_set_transform_2d
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_set_transform_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_set_transform_2d
             #-}

instance Method "multimesh_instance_set_transform_2d"
           GodotVisualServer
           (GodotRid -> Int -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_set_transform_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_set_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_set_color #-}

instance Method "multimesh_instance_set_color" GodotVisualServer
           (GodotRid -> Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_set_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_set_custom_data
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_set_custom_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_set_custom_data
             #-}

instance Method "multimesh_instance_set_custom_data"
           GodotVisualServer
           (GodotRid -> Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_set_custom_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_get_mesh
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_get_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_get_mesh #-}

instance Method "multimesh_get_mesh" GodotVisualServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_multimesh_get_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_get_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_get_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_get_aabb #-}

instance Method "multimesh_get_aabb" GodotVisualServer
           (GodotRid -> IO GodotAabb)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_multimesh_get_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_get_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_get_transform #-}

instance Method "multimesh_instance_get_transform"
           GodotVisualServer
           (GodotRid -> Int -> IO GodotTransform)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_get_transform_2d
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_get_transform_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_get_transform_2d
             #-}

instance Method "multimesh_instance_get_transform_2d"
           GodotVisualServer
           (GodotRid -> Int -> IO GodotTransform2d)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_get_transform_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_get_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_get_color #-}

instance Method "multimesh_instance_get_color" GodotVisualServer
           (GodotRid -> Int -> IO GodotColor)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_get_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_instance_get_custom_data
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_instance_get_custom_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_instance_get_custom_data
             #-}

instance Method "multimesh_instance_get_custom_data"
           GodotVisualServer
           (GodotRid -> Int -> IO GodotColor)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_instance_get_custom_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_set_visible_instances
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_set_visible_instances" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_set_visible_instances #-}

instance Method "multimesh_set_visible_instances" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_set_visible_instances
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_get_visible_instances
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_get_visible_instances" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_get_visible_instances #-}

instance Method "multimesh_get_visible_instances" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_multimesh_get_visible_instances
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_multimesh_set_as_bulk_array
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "multimesh_set_as_bulk_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_multimesh_set_as_bulk_array #-}

instance Method "multimesh_set_as_bulk_array" GodotVisualServer
           (GodotRid -> GodotPoolRealArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_multimesh_set_as_bulk_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_create #-}

instance Method "immediate_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_begin
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_begin #-}

instance Method "immediate_begin" GodotVisualServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_vertex
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_vertex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_vertex #-}

instance Method "immediate_vertex" GodotVisualServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_vertex
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_vertex_2d
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_vertex_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_vertex_2d #-}

instance Method "immediate_vertex_2d" GodotVisualServer
           (GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_vertex_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_normal
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_normal #-}

instance Method "immediate_normal" GodotVisualServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_tangent
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_tangent #-}

instance Method "immediate_tangent" GodotVisualServer
           (GodotRid -> GodotPlane -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_color #-}

instance Method "immediate_color" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_uv
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_uv #-}

instance Method "immediate_uv" GodotVisualServer
           (GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_uv (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_uv2
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_uv2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_uv2 #-}

instance Method "immediate_uv2" GodotVisualServer
           (GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_uv2 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_end
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_end #-}

instance Method "immediate_end" GodotVisualServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_end (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_clear
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_clear #-}

instance Method "immediate_clear" GodotVisualServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_clear
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_set_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_set_material #-}

instance Method "immediate_set_material" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_set_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_immediate_get_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "immediate_get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_immediate_get_material #-}

instance Method "immediate_get_material" GodotVisualServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_immediate_get_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_skeleton_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "skeleton_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_skeleton_create #-}

instance Method "skeleton_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_skeleton_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_skeleton_allocate
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "skeleton_allocate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_skeleton_allocate #-}

instance Method "skeleton_allocate" GodotVisualServer
           (GodotRid -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_skeleton_allocate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_skeleton_get_bone_count
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "skeleton_get_bone_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_skeleton_get_bone_count #-}

instance Method "skeleton_get_bone_count" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_skeleton_get_bone_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_skeleton_bone_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "skeleton_bone_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_skeleton_bone_set_transform #-}

instance Method "skeleton_bone_set_transform" GodotVisualServer
           (GodotRid -> Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_skeleton_bone_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_skeleton_bone_get_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "skeleton_bone_get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_skeleton_bone_get_transform #-}

instance Method "skeleton_bone_get_transform" GodotVisualServer
           (GodotRid -> Int -> IO GodotTransform)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_skeleton_bone_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_skeleton_bone_set_transform_2d
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "skeleton_bone_set_transform_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_skeleton_bone_set_transform_2d #-}

instance Method "skeleton_bone_set_transform_2d" GodotVisualServer
           (GodotRid -> Int -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_skeleton_bone_set_transform_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_skeleton_bone_get_transform_2d
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "skeleton_bone_get_transform_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_skeleton_bone_get_transform_2d #-}

instance Method "skeleton_bone_get_transform_2d" GodotVisualServer
           (GodotRid -> Int -> IO GodotTransform2d)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_skeleton_bone_get_transform_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_directional_light_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "directional_light_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_directional_light_create #-}

instance Method "directional_light_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_directional_light_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_omni_light_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "omni_light_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_omni_light_create #-}

instance Method "omni_light_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_omni_light_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_spot_light_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "spot_light_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_spot_light_create #-}

instance Method "spot_light_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_spot_light_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_color #-}

instance Method "light_set_color" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_set_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_param
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_param #-}

instance Method "light_set_param" GodotVisualServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_shadow
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_shadow" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_shadow #-}

instance Method "light_set_shadow" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_set_shadow
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_shadow_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_shadow_color #-}

instance Method "light_set_shadow_color" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_set_shadow_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_projector
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_projector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_projector #-}

instance Method "light_set_projector" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_set_projector
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_negative
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_negative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_negative #-}

instance Method "light_set_negative" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_set_negative
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_cull_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_cull_mask #-}

instance Method "light_set_cull_mask" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_set_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_set_reverse_cull_face_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_set_reverse_cull_face_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_set_reverse_cull_face_mode #-}

instance Method "light_set_reverse_cull_face_mode"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_light_set_reverse_cull_face_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_omni_set_shadow_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_omni_set_shadow_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_omni_set_shadow_mode #-}

instance Method "light_omni_set_shadow_mode" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_light_omni_set_shadow_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_omni_set_shadow_detail
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_omni_set_shadow_detail" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_omni_set_shadow_detail #-}

instance Method "light_omni_set_shadow_detail" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_light_omni_set_shadow_detail
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_directional_set_shadow_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_directional_set_shadow_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_directional_set_shadow_mode #-}

instance Method "light_directional_set_shadow_mode"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_light_directional_set_shadow_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_directional_set_blend_splits
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_directional_set_blend_splits" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_directional_set_blend_splits
             #-}

instance Method "light_directional_set_blend_splits"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_light_directional_set_blend_splits
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_light_directional_set_shadow_depth_range_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "light_directional_set_shadow_depth_range_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_light_directional_set_shadow_depth_range_mode
             #-}

instance Method "light_directional_set_shadow_depth_range_mode"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_light_directional_set_shadow_depth_range_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_create #-}

instance Method "reflection_probe_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_reflection_probe_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_update_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_update_mode #-}

instance Method "reflection_probe_set_update_mode"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_update_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_intensity
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_intensity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_intensity #-}

instance Method "reflection_probe_set_intensity" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_intensity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_interior_ambient
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_interior_ambient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_interior_ambient
             #-}

instance Method "reflection_probe_set_interior_ambient"
           GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_interior_ambient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_interior_ambient_energy
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_interior_ambient_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_interior_ambient_energy
             #-}

instance Method "reflection_probe_set_interior_ambient_energy"
           GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_interior_ambient_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_interior_ambient_probe_contribution
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString
            "reflection_probe_set_interior_ambient_probe_contribution"
            $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_interior_ambient_probe_contribution
             #-}

instance Method
           "reflection_probe_set_interior_ambient_probe_contribution"
           GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_interior_ambient_probe_contribution
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_max_distance
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_max_distance #-}

instance Method "reflection_probe_set_max_distance"
           GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_extents
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_extents #-}

instance Method "reflection_probe_set_extents" GodotVisualServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_origin_offset
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_origin_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_origin_offset
             #-}

instance Method "reflection_probe_set_origin_offset"
           GodotVisualServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_origin_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_as_interior
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_as_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_as_interior #-}

instance Method "reflection_probe_set_as_interior"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_as_interior
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_enable_box_projection
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_enable_box_projection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_enable_box_projection
             #-}

instance Method "reflection_probe_set_enable_box_projection"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_enable_box_projection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_enable_shadows
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_enable_shadows" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_enable_shadows
             #-}

instance Method "reflection_probe_set_enable_shadows"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_enable_shadows
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_reflection_probe_set_cull_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "reflection_probe_set_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_reflection_probe_set_cull_mask #-}

instance Method "reflection_probe_set_cull_mask" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_reflection_probe_set_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_create #-}

instance Method "gi_probe_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_bounds
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_bounds #-}

instance Method "gi_probe_set_bounds" GodotVisualServer
           (GodotRid -> GodotAabb -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_bounds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_bounds
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_bounds #-}

instance Method "gi_probe_get_bounds" GodotVisualServer
           (GodotRid -> IO GodotAabb)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_bounds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_cell_size
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_cell_size #-}

instance Method "gi_probe_set_cell_size" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_cell_size
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_cell_size #-}

instance Method "gi_probe_get_cell_size" GodotVisualServer
           (GodotRid -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_to_cell_xform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_to_cell_xform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_to_cell_xform #-}

instance Method "gi_probe_set_to_cell_xform" GodotVisualServer
           (GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_to_cell_xform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_to_cell_xform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_to_cell_xform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_to_cell_xform #-}

instance Method "gi_probe_get_to_cell_xform" GodotVisualServer
           (GodotRid -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_to_cell_xform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_dynamic_data
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_dynamic_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_dynamic_data #-}

instance Method "gi_probe_set_dynamic_data" GodotVisualServer
           (GodotRid -> GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_dynamic_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_dynamic_data
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_dynamic_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_dynamic_data #-}

instance Method "gi_probe_get_dynamic_data" GodotVisualServer
           (GodotRid -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_dynamic_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_dynamic_range
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_dynamic_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_dynamic_range #-}

instance Method "gi_probe_set_dynamic_range" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_dynamic_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_dynamic_range
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_dynamic_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_dynamic_range #-}

instance Method "gi_probe_get_dynamic_range" GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_dynamic_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_energy
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_energy #-}

instance Method "gi_probe_set_energy" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_energy
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_energy #-}

instance Method "gi_probe_get_energy" GodotVisualServer
           (GodotRid -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_bias
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_bias #-}

instance Method "gi_probe_set_bias" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_bias
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_bias
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_bias #-}

instance Method "gi_probe_get_bias" GodotVisualServer
           (GodotRid -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_bias
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_normal_bias
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_normal_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_normal_bias #-}

instance Method "gi_probe_set_normal_bias" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_normal_bias
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_normal_bias
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_normal_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_normal_bias #-}

instance Method "gi_probe_get_normal_bias" GodotVisualServer
           (GodotRid -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_normal_bias
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_propagation
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_propagation #-}

instance Method "gi_probe_set_propagation" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_propagation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_get_propagation
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_get_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_get_propagation #-}

instance Method "gi_probe_get_propagation" GodotVisualServer
           (GodotRid -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_get_propagation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_interior
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_interior #-}

instance Method "gi_probe_set_interior" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_interior
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_is_interior
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_is_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_is_interior #-}

instance Method "gi_probe_is_interior" GodotVisualServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_is_interior
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_set_compress
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_set_compress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_set_compress #-}

instance Method "gi_probe_set_compress" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_set_compress
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_gi_probe_is_compressed
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "gi_probe_is_compressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_gi_probe_is_compressed #-}

instance Method "gi_probe_is_compressed" GodotVisualServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_gi_probe_is_compressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_create #-}

instance Method "lightmap_capture_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_lightmap_capture_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_set_bounds
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_set_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_set_bounds #-}

instance Method "lightmap_capture_set_bounds" GodotVisualServer
           (GodotRid -> GodotAabb -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_lightmap_capture_set_bounds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_get_bounds
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_get_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_get_bounds #-}

instance Method "lightmap_capture_get_bounds" GodotVisualServer
           (GodotRid -> IO GodotAabb)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_lightmap_capture_get_bounds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_set_octree
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_set_octree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_set_octree #-}

instance Method "lightmap_capture_set_octree" GodotVisualServer
           (GodotRid -> GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_lightmap_capture_set_octree
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_set_octree_cell_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_set_octree_cell_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_set_octree_cell_transform
             #-}

instance Method "lightmap_capture_set_octree_cell_transform"
           GodotVisualServer
           (GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_lightmap_capture_set_octree_cell_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_get_octree_cell_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_get_octree_cell_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_get_octree_cell_transform
             #-}

instance Method "lightmap_capture_get_octree_cell_transform"
           GodotVisualServer
           (GodotRid -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_lightmap_capture_get_octree_cell_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_set_octree_cell_subdiv
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_set_octree_cell_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_set_octree_cell_subdiv
             #-}

instance Method "lightmap_capture_set_octree_cell_subdiv"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_lightmap_capture_set_octree_cell_subdiv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_get_octree_cell_subdiv
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_get_octree_cell_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_get_octree_cell_subdiv
             #-}

instance Method "lightmap_capture_get_octree_cell_subdiv"
           GodotVisualServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_lightmap_capture_get_octree_cell_subdiv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_get_octree
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_get_octree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_get_octree #-}

instance Method "lightmap_capture_get_octree" GodotVisualServer
           (GodotRid -> IO GodotPoolByteArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_lightmap_capture_get_octree
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_set_energy
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_set_energy #-}

instance Method "lightmap_capture_set_energy" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_lightmap_capture_set_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_lightmap_capture_get_energy
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "lightmap_capture_get_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_lightmap_capture_get_energy #-}

instance Method "lightmap_capture_get_energy" GodotVisualServer
           (GodotRid -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_lightmap_capture_get_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_create #-}

instance Method "particles_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_emitting
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_emitting #-}

instance Method "particles_set_emitting" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_emitting
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_get_emitting
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_get_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_get_emitting #-}

instance Method "particles_get_emitting" GodotVisualServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_get_emitting
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_amount
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_amount #-}

instance Method "particles_set_amount" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_lifetime
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_lifetime #-}

instance Method "particles_set_lifetime" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_lifetime
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_one_shot
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_one_shot #-}

instance Method "particles_set_one_shot" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_one_shot
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_pre_process_time
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_pre_process_time #-}

instance Method "particles_set_pre_process_time" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_explosiveness_ratio
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_explosiveness_ratio #-}

instance Method "particles_set_explosiveness_ratio"
           GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_randomness_ratio
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_randomness_ratio #-}

instance Method "particles_set_randomness_ratio" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_custom_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_custom_aabb #-}

instance Method "particles_set_custom_aabb" GodotVisualServer
           (GodotRid -> GodotAabb -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_custom_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_speed_scale
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_speed_scale #-}

instance Method "particles_set_speed_scale" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_use_local_coordinates
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_use_local_coordinates
             #-}

instance Method "particles_set_use_local_coordinates"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_process_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_process_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_process_material #-}

instance Method "particles_set_process_material" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_process_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_fixed_fps
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_fixed_fps #-}

instance Method "particles_set_fixed_fps" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_fixed_fps
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_fractional_delta
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_fractional_delta #-}

instance Method "particles_set_fractional_delta" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_restart
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_restart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_restart #-}

instance Method "particles_restart" GodotVisualServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_restart
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_draw_order
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_draw_order #-}

instance Method "particles_set_draw_order" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_draw_order
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_draw_passes
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_draw_passes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_draw_passes #-}

instance Method "particles_set_draw_passes" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_set_draw_passes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_draw_pass_mesh
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_draw_pass_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_draw_pass_mesh #-}

instance Method "particles_set_draw_pass_mesh" GodotVisualServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_draw_pass_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_get_current_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_get_current_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_get_current_aabb #-}

instance Method "particles_get_current_aabb" GodotVisualServer
           (GodotRid -> IO GodotAabb)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_particles_get_current_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_particles_set_emission_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "particles_set_emission_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_particles_set_emission_transform #-}

instance Method "particles_set_emission_transform"
           GodotVisualServer
           (GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_particles_set_emission_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_camera_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "camera_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_camera_create #-}

instance Method "camera_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_camera_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_camera_set_perspective
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "camera_set_perspective" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_camera_set_perspective #-}

instance Method "camera_set_perspective" GodotVisualServer
           (GodotRid -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_camera_set_perspective
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_camera_set_orthogonal
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "camera_set_orthogonal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_camera_set_orthogonal #-}

instance Method "camera_set_orthogonal" GodotVisualServer
           (GodotRid -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_camera_set_orthogonal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_camera_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "camera_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_camera_set_transform #-}

instance Method "camera_set_transform" GodotVisualServer
           (GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_camera_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_camera_set_cull_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "camera_set_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_camera_set_cull_mask #-}

instance Method "camera_set_cull_mask" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_camera_set_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_camera_set_environment
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "camera_set_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_camera_set_environment #-}

instance Method "camera_set_environment" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_camera_set_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_camera_set_use_vertical_aspect
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "camera_set_use_vertical_aspect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_camera_set_use_vertical_aspect #-}

instance Method "camera_set_use_vertical_aspect" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_camera_set_use_vertical_aspect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_create #-}

instance Method "viewport_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_use_arvr
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_use_arvr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_use_arvr #-}

instance Method "viewport_set_use_arvr" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_use_arvr
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_size
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_size #-}

instance Method "viewport_set_size" GodotVisualServer
           (GodotRid -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_active
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_active #-}

instance Method "viewport_set_active" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_parent_viewport
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_parent_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_parent_viewport #-}

instance Method "viewport_set_parent_viewport" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_parent_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_attach_to_screen
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_attach_to_screen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_attach_to_screen #-}

instance Method "viewport_attach_to_screen" GodotVisualServer
           (GodotRid -> GodotRect2 -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_attach_to_screen
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_detach
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_detach" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_detach #-}

instance Method "viewport_detach" GodotVisualServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_detach
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_update_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_update_mode #-}

instance Method "viewport_set_update_mode" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_update_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_vflip
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_vflip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_vflip #-}

instance Method "viewport_set_vflip" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_vflip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_clear_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_clear_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_clear_mode #-}

instance Method "viewport_set_clear_mode" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_clear_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_get_texture
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_get_texture #-}

instance Method "viewport_get_texture" GodotVisualServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_get_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_hide_scenario
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_hide_scenario" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_hide_scenario #-}

instance Method "viewport_set_hide_scenario" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_hide_scenario
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_hide_canvas
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_hide_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_hide_canvas #-}

instance Method "viewport_set_hide_canvas" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_hide_canvas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_disable_environment
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_disable_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_disable_environment #-}

instance Method "viewport_set_disable_environment"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_disable_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_disable_3d
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_disable_3d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_disable_3d #-}

instance Method "viewport_set_disable_3d" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_disable_3d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_attach_camera
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_attach_camera" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_attach_camera #-}

instance Method "viewport_attach_camera" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_attach_camera
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_scenario
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_scenario" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_scenario #-}

instance Method "viewport_set_scenario" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_scenario
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_attach_canvas
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_attach_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_attach_canvas #-}

instance Method "viewport_attach_canvas" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_attach_canvas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_remove_canvas
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_remove_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_remove_canvas #-}

instance Method "viewport_remove_canvas" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_remove_canvas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_canvas_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_canvas_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_canvas_transform #-}

instance Method "viewport_set_canvas_transform" GodotVisualServer
           (GodotRid -> GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_canvas_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_transparent_background
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_transparent_background" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_transparent_background
             #-}

instance Method "viewport_set_transparent_background"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_transparent_background
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_global_canvas_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_global_canvas_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_global_canvas_transform
             #-}

instance Method "viewport_set_global_canvas_transform"
           GodotVisualServer
           (GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_global_canvas_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_canvas_stacking
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_canvas_stacking" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_canvas_stacking #-}

instance Method "viewport_set_canvas_stacking" GodotVisualServer
           (GodotRid -> GodotRid -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_canvas_stacking
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_shadow_atlas_size
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_shadow_atlas_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_shadow_atlas_size #-}

instance Method "viewport_set_shadow_atlas_size" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_shadow_atlas_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_shadow_atlas_quadrant_subdivision
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_shadow_atlas_quadrant_subdivision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_shadow_atlas_quadrant_subdivision
             #-}

instance Method "viewport_set_shadow_atlas_quadrant_subdivision"
           GodotVisualServer
           (GodotRid -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_viewport_set_shadow_atlas_quadrant_subdivision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_msaa
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_msaa" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_msaa #-}

instance Method "viewport_set_msaa" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_msaa
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_hdr
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_hdr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_hdr #-}

instance Method "viewport_set_hdr" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_hdr
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_usage
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_usage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_usage #-}

instance Method "viewport_set_usage" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_usage
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_get_render_info
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_get_render_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_get_render_info #-}

instance Method "viewport_get_render_info" GodotVisualServer
           (GodotRid -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_get_render_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_viewport_set_debug_draw
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "viewport_set_debug_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_viewport_set_debug_draw #-}

instance Method "viewport_set_debug_draw" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_viewport_set_debug_draw
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_create #-}

instance Method "environment_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_background
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_background" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_background #-}

instance Method "environment_set_background" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_background
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_sky
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_sky" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_sky #-}

instance Method "environment_set_sky" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_sky
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_sky_custom_fov
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_sky_custom_fov" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_sky_custom_fov #-}

instance Method "environment_set_sky_custom_fov" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_environment_set_sky_custom_fov
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_bg_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_bg_color #-}

instance Method "environment_set_bg_color" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_bg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_bg_energy
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_bg_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_bg_energy #-}

instance Method "environment_set_bg_energy" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_bg_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_canvas_max_layer
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_canvas_max_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_canvas_max_layer #-}

instance Method "environment_set_canvas_max_layer"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_environment_set_canvas_max_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_ambient_light
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_ambient_light" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_ambient_light #-}

instance Method "environment_set_ambient_light" GodotVisualServer
           (GodotRid -> GodotColor -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_environment_set_ambient_light
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_dof_blur_near
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_dof_blur_near" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_dof_blur_near #-}

instance Method "environment_set_dof_blur_near" GodotVisualServer
           (GodotRid -> Bool -> Float -> Float -> Float -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_environment_set_dof_blur_near
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_dof_blur_far
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_dof_blur_far" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_dof_blur_far #-}

instance Method "environment_set_dof_blur_far" GodotVisualServer
           (GodotRid -> Bool -> Float -> Float -> Float -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_environment_set_dof_blur_far
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_glow
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_glow" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_glow #-}

instance Method "environment_set_glow" GodotVisualServer
           (GodotRid ->
              Bool ->
                Int ->
                  Float -> Float -> Float -> Int -> Float -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9, toVariant arg10]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_glow
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_tonemap
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_tonemap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_tonemap #-}

instance Method "environment_set_tonemap" GodotVisualServer
           (GodotRid ->
              Int ->
                Float ->
                  Float -> Bool -> Float -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_tonemap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_adjustment
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_adjustment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_adjustment #-}

instance Method "environment_set_adjustment" GodotVisualServer
           (GodotRid -> Bool -> Float -> Float -> Float -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_adjustment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_ssr
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_ssr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_ssr #-}

instance Method "environment_set_ssr" GodotVisualServer
           (GodotRid ->
              Bool -> Int -> Float -> Float -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_ssr
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_ssao
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_ssao" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_ssao #-}

instance Method "environment_set_ssao" GodotVisualServer
           (GodotRid ->
              Bool ->
                Float ->
                  Float ->
                    Float ->
                      Float ->
                        Float ->
                          Float -> Float -> GodotColor -> Int -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10
          arg11 arg12 arg13
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9, toVariant arg10, toVariant arg11, toVariant arg12,
               toVariant arg13]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_ssao
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_fog
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_fog" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_fog #-}

instance Method "environment_set_fog" GodotVisualServer
           (GodotRid -> Bool -> GodotColor -> GodotColor -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_fog
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_fog_depth
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_fog_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_fog_depth #-}

instance Method "environment_set_fog_depth" GodotVisualServer
           (GodotRid -> Bool -> Float -> Float -> Bool -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_fog_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_environment_set_fog_height
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "environment_set_fog_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_environment_set_fog_height #-}

instance Method "environment_set_fog_height" GodotVisualServer
           (GodotRid -> Bool -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_environment_set_fog_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_scenario_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "scenario_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_scenario_create #-}

instance Method "scenario_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_scenario_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_scenario_set_debug
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "scenario_set_debug" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_scenario_set_debug #-}

instance Method "scenario_set_debug" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_scenario_set_debug
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_scenario_set_environment
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "scenario_set_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_scenario_set_environment #-}

instance Method "scenario_set_environment" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_scenario_set_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_scenario_set_reflection_atlas_size
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "scenario_set_reflection_atlas_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_scenario_set_reflection_atlas_size
             #-}

instance Method "scenario_set_reflection_atlas_size"
           GodotVisualServer
           (GodotRid -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_scenario_set_reflection_atlas_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_scenario_set_fallback_environment
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "scenario_set_fallback_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_scenario_set_fallback_environment #-}

instance Method "scenario_set_fallback_environment"
           GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_scenario_set_fallback_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_create2
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_create2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_create2 #-}

instance Method "instance_create2" GodotVisualServer
           (GodotRid -> GodotRid -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_create2
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_create #-}

instance Method "instance_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_base
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_base" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_base #-}

instance Method "instance_set_base" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_base
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_scenario
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_scenario" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_scenario #-}

instance Method "instance_set_scenario" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_scenario
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_layer_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_layer_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_layer_mask #-}

instance Method "instance_set_layer_mask" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_layer_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_transform #-}

instance Method "instance_set_transform" GodotVisualServer
           (GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_attach_object_instance_id
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_attach_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_attach_object_instance_id
             #-}

instance Method "instance_attach_object_instance_id"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_attach_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_blend_shape_weight
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_blend_shape_weight" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_blend_shape_weight #-}

instance Method "instance_set_blend_shape_weight" GodotVisualServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_set_blend_shape_weight
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_surface_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_surface_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_surface_material #-}

instance Method "instance_set_surface_material" GodotVisualServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_set_surface_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_visible
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_visible #-}

instance Method "instance_set_visible" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_use_lightmap
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_use_lightmap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_use_lightmap #-}

instance Method "instance_set_use_lightmap" GodotVisualServer
           (GodotRid -> GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_use_lightmap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_custom_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_custom_aabb #-}

instance Method "instance_set_custom_aabb" GodotVisualServer
           (GodotRid -> GodotAabb -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_custom_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_attach_skeleton
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_attach_skeleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_attach_skeleton #-}

instance Method "instance_attach_skeleton" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_attach_skeleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_exterior
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_exterior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_exterior #-}

instance Method "instance_set_exterior" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_set_exterior
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_set_extra_visibility_margin
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_set_extra_visibility_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_set_extra_visibility_margin
             #-}

instance Method "instance_set_extra_visibility_margin"
           GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_set_extra_visibility_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_geometry_set_flag
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_geometry_set_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_geometry_set_flag #-}

instance Method "instance_geometry_set_flag" GodotVisualServer
           (GodotRid -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instance_geometry_set_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_geometry_set_cast_shadows_setting
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_geometry_set_cast_shadows_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_geometry_set_cast_shadows_setting
             #-}

instance Method "instance_geometry_set_cast_shadows_setting"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_geometry_set_cast_shadows_setting
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_geometry_set_material_override
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_geometry_set_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_geometry_set_material_override
             #-}

instance Method "instance_geometry_set_material_override"
           GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_geometry_set_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_geometry_set_draw_range
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_geometry_set_draw_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_geometry_set_draw_range #-}

instance Method "instance_geometry_set_draw_range"
           GodotVisualServer
           (GodotRid -> Float -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_geometry_set_draw_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instance_geometry_set_as_instance_lod
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instance_geometry_set_as_instance_lod" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instance_geometry_set_as_instance_lod
             #-}

instance Method "instance_geometry_set_as_instance_lod"
           GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_instance_geometry_set_as_instance_lod
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instances_cull_aabb
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instances_cull_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instances_cull_aabb #-}

instance Method "instances_cull_aabb" GodotVisualServer
           (GodotAabb -> GodotRid -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instances_cull_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instances_cull_ray
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instances_cull_ray" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instances_cull_ray #-}

instance Method "instances_cull_ray" GodotVisualServer
           (GodotVector3 -> GodotVector3 -> GodotRid -> IO GodotArray)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instances_cull_ray
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_instances_cull_convex
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "instances_cull_convex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_instances_cull_convex #-}

instance Method "instances_cull_convex" GodotVisualServer
           (GodotArray -> GodotRid -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_instances_cull_convex
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_create #-}

instance Method "canvas_create" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_set_item_mirroring
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_set_item_mirroring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_set_item_mirroring #-}

instance Method "canvas_set_item_mirroring" GodotVisualServer
           (GodotRid -> GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_set_item_mirroring
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_set_modulate
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_set_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_set_modulate #-}

instance Method "canvas_set_modulate" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_set_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_create #-}

instance Method "canvas_item_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_parent
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_parent #-}

instance Method "canvas_item_set_parent" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_parent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_visible
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_visible #-}

instance Method "canvas_item_set_visible" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_light_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_light_mask #-}

instance Method "canvas_item_set_light_mask" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_light_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_transform #-}

instance Method "canvas_item_set_transform" GodotVisualServer
           (GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_clip
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_clip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_clip #-}

instance Method "canvas_item_set_clip" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_clip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_distance_field_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_distance_field_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_distance_field_mode
             #-}

instance Method "canvas_item_set_distance_field_mode"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_set_distance_field_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_custom_rect
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_custom_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_custom_rect #-}

instance Method "canvas_item_set_custom_rect" GodotVisualServer
           (GodotRid -> Bool -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_custom_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_modulate
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_modulate #-}

instance Method "canvas_item_set_modulate" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_self_modulate
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_self_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_self_modulate #-}

instance Method "canvas_item_set_self_modulate" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_set_self_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_draw_behind_parent
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_draw_behind_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_draw_behind_parent
             #-}

instance Method "canvas_item_set_draw_behind_parent"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_set_draw_behind_parent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_line
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_line #-}

instance Method "canvas_item_add_line" GodotVisualServer
           (GodotRid ->
              GodotVector2 ->
                GodotVector2 -> GodotColor -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_polyline
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_polyline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_polyline #-}

instance Method "canvas_item_add_polyline" GodotVisualServer
           (GodotRid ->
              GodotPoolVector2Array ->
                GodotPoolColorArray -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_polyline
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_rect
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_rect #-}

instance Method "canvas_item_add_rect" GodotVisualServer
           (GodotRid -> GodotRect2 -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_circle
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_circle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_circle #-}

instance Method "canvas_item_add_circle" GodotVisualServer
           (GodotRid -> GodotVector2 -> Float -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_circle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_texture_rect
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_texture_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_texture_rect #-}

instance Method "canvas_item_add_texture_rect" GodotVisualServer
           (GodotRid ->
              GodotRect2 ->
                GodotRid -> Bool -> GodotColor -> Bool -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_add_texture_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_texture_rect_region
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_texture_rect_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_texture_rect_region
             #-}

instance Method "canvas_item_add_texture_rect_region"
           GodotVisualServer
           (GodotRid ->
              GodotRect2 ->
                GodotRid ->
                  GodotRect2 -> GodotColor -> Bool -> GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_add_texture_rect_region
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_nine_patch
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_nine_patch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_nine_patch #-}

instance Method "canvas_item_add_nine_patch" GodotVisualServer
           (GodotRid ->
              GodotRect2 ->
                GodotRect2 ->
                  GodotRid ->
                    GodotVector2 ->
                      GodotVector2 ->
                        Int -> Int -> Bool -> GodotColor -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10
          arg11
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9, toVariant arg10, toVariant arg11]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_nine_patch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_primitive
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_primitive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_primitive #-}

instance Method "canvas_item_add_primitive" GodotVisualServer
           (GodotRid ->
              GodotPoolVector2Array ->
                GodotPoolColorArray ->
                  GodotPoolVector2Array -> GodotRid -> Float -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_primitive
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_polygon
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_polygon #-}

instance Method "canvas_item_add_polygon" GodotVisualServer
           (GodotRid ->
              GodotPoolVector2Array ->
                GodotPoolColorArray ->
                  GodotPoolVector2Array -> GodotRid -> GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_triangle_array
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_triangle_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_triangle_array #-}

instance Method "canvas_item_add_triangle_array" GodotVisualServer
           (GodotRid ->
              GodotPoolIntArray ->
                GodotPoolVector2Array ->
                  GodotPoolColorArray ->
                    GodotPoolVector2Array ->
                      GodotPoolIntArray ->
                        GodotPoolRealArray -> GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9, toVariant arg10]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_add_triangle_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_mesh
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_mesh #-}

instance Method "canvas_item_add_mesh" GodotVisualServer
           (GodotRid -> GodotRid -> GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_multimesh
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_multimesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_multimesh #-}

instance Method "canvas_item_add_multimesh" GodotVisualServer
           (GodotRid -> GodotRid -> GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_multimesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_particles
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_particles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_particles #-}

instance Method "canvas_item_add_particles" GodotVisualServer
           (GodotRid ->
              GodotRid -> GodotRid -> GodotRid -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_particles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_set_transform #-}

instance Method "canvas_item_add_set_transform" GodotVisualServer
           (GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_add_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_add_clip_ignore
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_add_clip_ignore" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_add_clip_ignore #-}

instance Method "canvas_item_add_clip_ignore" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_add_clip_ignore
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_sort_children_by_y
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_sort_children_by_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_sort_children_by_y
             #-}

instance Method "canvas_item_set_sort_children_by_y"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_set_sort_children_by_y
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_z_index
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_z_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_z_index #-}

instance Method "canvas_item_set_z_index" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_z_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_z_as_relative_to_parent
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_z_as_relative_to_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_z_as_relative_to_parent
             #-}

instance Method "canvas_item_set_z_as_relative_to_parent"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_set_z_as_relative_to_parent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_copy_to_backbuffer
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_copy_to_backbuffer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_copy_to_backbuffer
             #-}

instance Method "canvas_item_set_copy_to_backbuffer"
           GodotVisualServer
           (GodotRid -> Bool -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_set_copy_to_backbuffer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_clear
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_clear #-}

instance Method "canvas_item_clear" GodotVisualServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_clear
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_draw_index
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_draw_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_draw_index #-}

instance Method "canvas_item_set_draw_index" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_draw_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_material #-}

instance Method "canvas_item_set_material" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_item_set_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_item_set_use_parent_material
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_item_set_use_parent_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_item_set_use_parent_material
             #-}

instance Method "canvas_item_set_use_parent_material"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_item_set_use_parent_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_create #-}

instance Method "canvas_light_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_attach_to_canvas
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_attach_to_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_attach_to_canvas #-}

instance Method "canvas_light_attach_to_canvas" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_attach_to_canvas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_enabled
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_enabled #-}

instance Method "canvas_light_set_enabled" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_scale
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_scale #-}

instance Method "canvas_light_set_scale" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_transform #-}

instance Method "canvas_light_set_transform" GodotVisualServer
           (GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_texture
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_texture #-}

instance Method "canvas_light_set_texture" GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_texture_offset
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_texture_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_texture_offset #-}

instance Method "canvas_light_set_texture_offset" GodotVisualServer
           (GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_texture_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_color #-}

instance Method "canvas_light_set_color" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_height
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_height #-}

instance Method "canvas_light_set_height" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_energy
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_energy #-}

instance Method "canvas_light_set_energy" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_z_range
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_z_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_z_range #-}

instance Method "canvas_light_set_z_range" GodotVisualServer
           (GodotRid -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_z_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_layer_range
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_layer_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_layer_range #-}

instance Method "canvas_light_set_layer_range" GodotVisualServer
           (GodotRid -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_layer_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_item_cull_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_item_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_item_cull_mask #-}

instance Method "canvas_light_set_item_cull_mask" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_item_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_item_shadow_cull_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_item_shadow_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_item_shadow_cull_mask
             #-}

instance Method "canvas_light_set_item_shadow_cull_mask"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_item_shadow_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_mode #-}

instance Method "canvas_light_set_mode" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_canvas_light_set_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_shadow_enabled
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_shadow_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_shadow_enabled #-}

instance Method "canvas_light_set_shadow_enabled" GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_shadow_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_shadow_buffer_size
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_shadow_buffer_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_shadow_buffer_size
             #-}

instance Method "canvas_light_set_shadow_buffer_size"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_shadow_buffer_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_shadow_gradient_length
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_shadow_gradient_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_shadow_gradient_length
             #-}

instance Method "canvas_light_set_shadow_gradient_length"
           GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_shadow_gradient_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_shadow_filter
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_shadow_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_shadow_filter #-}

instance Method "canvas_light_set_shadow_filter" GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_shadow_filter
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_shadow_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_shadow_color #-}

instance Method "canvas_light_set_shadow_color" GodotVisualServer
           (GodotRid -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_shadow_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_set_shadow_smooth
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_set_shadow_smooth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_set_shadow_smooth #-}

instance Method "canvas_light_set_shadow_smooth" GodotVisualServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_set_shadow_smooth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_occluder_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_occluder_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_occluder_create #-}

instance Method "canvas_light_occluder_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_occluder_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_occluder_attach_to_canvas
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_occluder_attach_to_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_occluder_attach_to_canvas
             #-}

instance Method "canvas_light_occluder_attach_to_canvas"
           GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_occluder_attach_to_canvas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_occluder_set_enabled
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_occluder_set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_occluder_set_enabled #-}

instance Method "canvas_light_occluder_set_enabled"
           GodotVisualServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_occluder_set_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_occluder_set_polygon
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_occluder_set_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_occluder_set_polygon #-}

instance Method "canvas_light_occluder_set_polygon"
           GodotVisualServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_occluder_set_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_occluder_set_transform
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_occluder_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_occluder_set_transform
             #-}

instance Method "canvas_light_occluder_set_transform"
           GodotVisualServer
           (GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_occluder_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_light_occluder_set_light_mask
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_light_occluder_set_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_light_occluder_set_light_mask
             #-}

instance Method "canvas_light_occluder_set_light_mask"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_light_occluder_set_light_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_occluder_polygon_create
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_occluder_polygon_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_occluder_polygon_create #-}

instance Method "canvas_occluder_polygon_create" GodotVisualServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_occluder_polygon_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_occluder_polygon_set_shape
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_occluder_polygon_set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_occluder_polygon_set_shape #-}

instance Method "canvas_occluder_polygon_set_shape"
           GodotVisualServer
           (GodotRid -> GodotPoolVector2Array -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_occluder_polygon_set_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_occluder_polygon_set_shape_as_lines
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_occluder_polygon_set_shape_as_lines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_occluder_polygon_set_shape_as_lines
             #-}

instance Method "canvas_occluder_polygon_set_shape_as_lines"
           GodotVisualServer
           (GodotRid -> GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_occluder_polygon_set_shape_as_lines
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_canvas_occluder_polygon_set_cull_mode
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "canvas_occluder_polygon_set_cull_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_canvas_occluder_polygon_set_cull_mode
             #-}

instance Method "canvas_occluder_polygon_set_cull_mode"
           GodotVisualServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_canvas_occluder_polygon_set_cull_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_black_bars_set_margins
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "black_bars_set_margins" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_black_bars_set_margins #-}

instance Method "black_bars_set_margins" GodotVisualServer
           (Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_black_bars_set_margins
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_black_bars_set_images
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "black_bars_set_images" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_black_bars_set_images #-}

instance Method "black_bars_set_images" GodotVisualServer
           (GodotRid -> GodotRid -> GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_black_bars_set_images
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_free_rid
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "free_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_free_rid #-}

instance Method "free_rid" GodotVisualServer (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_free_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_request_frame_drawn_callback
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "request_frame_drawn_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_request_frame_drawn_callback #-}

instance Method "request_frame_drawn_callback" GodotVisualServer
           (GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_request_frame_drawn_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_has_changed
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "has_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_has_changed #-}

instance Method "has_changed" GodotVisualServer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_has_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_init
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "init" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_init #-}

instance Method "init" GodotVisualServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_init (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_finish
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "finish" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_finish #-}

instance Method "finish" GodotVisualServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_finish (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_get_render_info
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "get_render_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_get_render_info #-}

instance Method "get_render_info" GodotVisualServer (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_get_render_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_make_sphere_mesh
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "make_sphere_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_make_sphere_mesh #-}

instance Method "make_sphere_mesh" GodotVisualServer
           (Int -> Int -> Float -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_make_sphere_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_get_test_cube
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "get_test_cube" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_get_test_cube #-}

instance Method "get_test_cube" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_get_test_cube (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_get_test_texture
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "get_test_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_get_test_texture #-}

instance Method "get_test_texture" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_get_test_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_get_white_texture
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "get_white_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_get_white_texture #-}

instance Method "get_white_texture" GodotVisualServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_get_white_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_set_boot_image
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "set_boot_image" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_set_boot_image #-}

instance Method "set_boot_image" GodotVisualServer
           (GodotImage -> GodotColor -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_set_boot_image (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_set_default_clear_color
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "set_default_clear_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_set_default_clear_color #-}

instance Method "set_default_clear_color" GodotVisualServer
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_set_default_clear_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_has_feature
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "has_feature" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_has_feature #-}

instance Method "has_feature" GodotVisualServer (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_has_feature (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_has_os_feature
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "has_os_feature" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_has_os_feature #-}

instance Method "has_os_feature" GodotVisualServer
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualServer_has_os_feature (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualServer_set_debug_generate_wireframes
  = unsafePerformIO $
      withCString "VisualServer" $
        \ clsNamePtr ->
          withCString "set_debug_generate_wireframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualServer_set_debug_generate_wireframes #-}

instance Method "set_debug_generate_wireframes" GodotVisualServer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualServer_set_debug_generate_wireframes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInput = GodotInput GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotInput where
        type BaseClass GodotInput = GodotObject
        super = coerce
bindInput_is_key_pressed
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "is_key_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_is_key_pressed #-}

instance Method "is_key_pressed" GodotInput (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_is_key_pressed (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_is_mouse_button_pressed
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "is_mouse_button_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_is_mouse_button_pressed #-}

instance Method "is_mouse_button_pressed" GodotInput
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_is_mouse_button_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_is_joy_button_pressed
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "is_joy_button_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_is_joy_button_pressed #-}

instance Method "is_joy_button_pressed" GodotInput
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_is_joy_button_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_is_action_pressed
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "is_action_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_is_action_pressed #-}

instance Method "is_action_pressed" GodotInput
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_is_action_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_is_action_just_pressed
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "is_action_just_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_is_action_just_pressed #-}

instance Method "is_action_just_pressed" GodotInput
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_is_action_just_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_is_action_just_released
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "is_action_just_released" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_is_action_just_released #-}

instance Method "is_action_just_released" GodotInput
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_is_action_just_released
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_action_strength
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_action_strength" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_action_strength #-}

instance Method "get_action_strength" GodotInput
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_action_strength (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_add_joy_mapping
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "add_joy_mapping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_add_joy_mapping #-}

instance Method "add_joy_mapping" GodotInput
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_add_joy_mapping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_remove_joy_mapping
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "remove_joy_mapping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_remove_joy_mapping #-}

instance Method "remove_joy_mapping" GodotInput
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_remove_joy_mapping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_joy_connection_changed
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "joy_connection_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_joy_connection_changed #-}

instance Method "joy_connection_changed" GodotInput
           (Int -> Bool -> GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_joy_connection_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_is_joy_known
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "is_joy_known" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_is_joy_known #-}

instance Method "is_joy_known" GodotInput (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_is_joy_known (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_axis
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_axis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_axis #-}

instance Method "get_joy_axis" GodotInput (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_axis (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_name
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_name #-}

instance Method "get_joy_name" GodotInput (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_name (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_guid
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_guid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_guid #-}

instance Method "get_joy_guid" GodotInput (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_guid (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_connected_joypads
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_connected_joypads" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_connected_joypads #-}

instance Method "get_connected_joypads" GodotInput (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_connected_joypads (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_vibration_strength
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_vibration_strength" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_vibration_strength #-}

instance Method "get_joy_vibration_strength" GodotInput
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_vibration_strength
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_vibration_duration
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_vibration_duration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_vibration_duration #-}

instance Method "get_joy_vibration_duration" GodotInput
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_vibration_duration
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_button_string
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_button_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_button_string #-}

instance Method "get_joy_button_string" GodotInput
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_button_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_button_index_from_string
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_button_index_from_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_button_index_from_string #-}

instance Method "get_joy_button_index_from_string" GodotInput
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_button_index_from_string
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_axis_string
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_axis_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_axis_string #-}

instance Method "get_joy_axis_string" GodotInput
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_axis_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_joy_axis_index_from_string
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_joy_axis_index_from_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_joy_axis_index_from_string #-}

instance Method "get_joy_axis_index_from_string" GodotInput
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_joy_axis_index_from_string
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_start_joy_vibration
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "start_joy_vibration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_start_joy_vibration #-}

instance Method "start_joy_vibration" GodotInput
           (Int -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_start_joy_vibration (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_stop_joy_vibration
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "stop_joy_vibration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_stop_joy_vibration #-}

instance Method "stop_joy_vibration" GodotInput (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_stop_joy_vibration (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_gravity
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_gravity #-}

instance Method "get_gravity" GodotInput (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_gravity (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_accelerometer
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_accelerometer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_accelerometer #-}

instance Method "get_accelerometer" GodotInput (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_accelerometer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_magnetometer
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_magnetometer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_magnetometer #-}

instance Method "get_magnetometer" GodotInput (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_magnetometer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_gyroscope
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_gyroscope" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_gyroscope #-}

instance Method "get_gyroscope" GodotInput (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_gyroscope (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_last_mouse_speed
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_last_mouse_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_last_mouse_speed #-}

instance Method "get_last_mouse_speed" GodotInput (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_last_mouse_speed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_mouse_button_mask
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_mouse_button_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_mouse_button_mask #-}

instance Method "get_mouse_button_mask" GodotInput (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_mouse_button_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_set_mouse_mode
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "set_mouse_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_set_mouse_mode #-}

instance Method "set_mouse_mode" GodotInput (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_set_mouse_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_get_mouse_mode
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "get_mouse_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_get_mouse_mode #-}

instance Method "get_mouse_mode" GodotInput (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_get_mouse_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_warp_mouse_position
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "warp_mouse_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_warp_mouse_position #-}

instance Method "warp_mouse_position" GodotInput
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_warp_mouse_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_action_press
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "action_press" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_action_press #-}

instance Method "action_press" GodotInput (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_action_press (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_action_release
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "action_release" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_action_release #-}

instance Method "action_release" GodotInput (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_action_release (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_set_default_cursor_shape
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "set_default_cursor_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_set_default_cursor_shape #-}

instance Method "set_default_cursor_shape" GodotInput
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_set_default_cursor_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_set_custom_mouse_cursor
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "set_custom_mouse_cursor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_set_custom_mouse_cursor #-}

instance Method "set_custom_mouse_cursor" GodotInput
           (GodotResource -> Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_set_custom_mouse_cursor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInput_parse_input_event
  = unsafePerformIO $
      withCString "Input" $
        \ clsNamePtr ->
          withCString "parse_input_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInput_parse_input_event #-}

instance Method "parse_input_event" GodotInput
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInput_parse_input_event (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInputDefault = GodotInputDefault GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotInputDefault where
        type BaseClass GodotInputDefault = GodotInput
        super = coerce

newtype GodotAudioServer = GodotAudioServer GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotAudioServer where
        type BaseClass GodotAudioServer = GodotObject
        super = coerce
bindAudioServer_set_bus_count
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_count #-}

instance Method "set_bus_count" GodotAudioServer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_count
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_count #-}

instance Method "get_bus_count" GodotAudioServer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_remove_bus
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "remove_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_remove_bus #-}

instance Method "remove_bus" GodotAudioServer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_remove_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_add_bus
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "add_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_add_bus #-}

instance Method "add_bus" GodotAudioServer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_add_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_move_bus
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "move_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_move_bus #-}

instance Method "move_bus" GodotAudioServer (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_move_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_name
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_name #-}

instance Method "set_bus_name" GodotAudioServer
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_name
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_name #-}

instance Method "get_bus_name" GodotAudioServer
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_index
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_index #-}

instance Method "get_bus_index" GodotAudioServer
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_index (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_volume_db
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_volume_db #-}

instance Method "set_bus_volume_db" GodotAudioServer
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_volume_db
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_volume_db #-}

instance Method "get_bus_volume_db" GodotAudioServer
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_send
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_send" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_send #-}

instance Method "set_bus_send" GodotAudioServer
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_send (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_send
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_send" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_send #-}

instance Method "get_bus_send" GodotAudioServer
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_send (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_solo
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_solo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_solo #-}

instance Method "set_bus_solo" GodotAudioServer
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_solo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_is_bus_solo
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "is_bus_solo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_is_bus_solo #-}

instance Method "is_bus_solo" GodotAudioServer (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_is_bus_solo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_mute
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_mute" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_mute #-}

instance Method "set_bus_mute" GodotAudioServer
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_mute (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_is_bus_mute
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "is_bus_mute" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_is_bus_mute #-}

instance Method "is_bus_mute" GodotAudioServer (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_is_bus_mute (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_bypass_effects
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_bypass_effects" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_bypass_effects #-}

instance Method "set_bus_bypass_effects" GodotAudioServer
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_bypass_effects
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_is_bus_bypassing_effects
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "is_bus_bypassing_effects" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_is_bus_bypassing_effects #-}

instance Method "is_bus_bypassing_effects" GodotAudioServer
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_is_bus_bypassing_effects
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_add_bus_effect
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "add_bus_effect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_add_bus_effect #-}

instance Method "add_bus_effect" GodotAudioServer
           (Int -> GodotAudioEffect -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_add_bus_effect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_remove_bus_effect
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "remove_bus_effect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_remove_bus_effect #-}

instance Method "remove_bus_effect" GodotAudioServer
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_remove_bus_effect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_effect_count
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_effect_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_effect_count #-}

instance Method "get_bus_effect_count" GodotAudioServer
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_effect_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_effect
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_effect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_effect #-}

instance Method "get_bus_effect" GodotAudioServer
           (Int -> Int -> IO GodotAudioEffect)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_effect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_swap_bus_effects
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "swap_bus_effects" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_swap_bus_effects #-}

instance Method "swap_bus_effects" GodotAudioServer
           (Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_swap_bus_effects
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_effect_enabled
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_effect_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_effect_enabled #-}

instance Method "set_bus_effect_enabled" GodotAudioServer
           (Int -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_effect_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_is_bus_effect_enabled
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "is_bus_effect_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_is_bus_effect_enabled #-}

instance Method "is_bus_effect_enabled" GodotAudioServer
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_is_bus_effect_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_peak_volume_left_db
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_peak_volume_left_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_peak_volume_left_db #-}

instance Method "get_bus_peak_volume_left_db" GodotAudioServer
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_peak_volume_left_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_bus_peak_volume_right_db
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_bus_peak_volume_right_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_bus_peak_volume_right_db #-}

instance Method "get_bus_peak_volume_right_db" GodotAudioServer
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_bus_peak_volume_right_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_lock
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_lock #-}

instance Method "lock" GodotAudioServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_lock (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_unlock
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "unlock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_unlock #-}

instance Method "unlock" GodotAudioServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_unlock (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_speaker_mode
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_speaker_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_speaker_mode #-}

instance Method "get_speaker_mode" GodotAudioServer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_speaker_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_mix_rate
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_mix_rate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_mix_rate #-}

instance Method "get_mix_rate" GodotAudioServer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_mix_rate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_device_list
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_device_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_device_list #-}

instance Method "get_device_list" GodotAudioServer (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_device_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_get_device
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "get_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_get_device #-}

instance Method "get_device" GodotAudioServer (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_get_device (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_device
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_device #-}

instance Method "set_device" GodotAudioServer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_device (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_capture_get_device_list
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "capture_get_device_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_capture_get_device_list #-}

instance Method "capture_get_device_list" GodotAudioServer
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_capture_get_device_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_capture_get_device
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "capture_get_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_capture_get_device #-}

instance Method "capture_get_device" GodotAudioServer
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_capture_get_device
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_capture_set_device
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "capture_set_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_capture_set_device #-}

instance Method "capture_set_device" GodotAudioServer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_capture_set_device
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_set_bus_layout
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "set_bus_layout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_set_bus_layout #-}

instance Method "set_bus_layout" GodotAudioServer
           (GodotAudioBusLayout -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_set_bus_layout (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioServer_generate_bus_layout
  = unsafePerformIO $
      withCString "AudioServer" $
        \ clsNamePtr ->
          withCString "generate_bus_layout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioServer_generate_bus_layout #-}

instance Method "generate_bus_layout" GodotAudioServer
           (IO GodotAudioBusLayout)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioServer_generate_bus_layout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotARVRServer = GodotARVRServer GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotARVRServer where
        type BaseClass GodotARVRServer = GodotObject
        super = coerce
bindARVRServer_get_world_scale
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_world_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_world_scale #-}

instance Method "get_world_scale" GodotARVRServer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_world_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_set_world_scale
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "set_world_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_set_world_scale #-}

instance Method "set_world_scale" GodotARVRServer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_set_world_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_reference_frame
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_reference_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_reference_frame #-}

instance Method "get_reference_frame" GodotARVRServer
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_reference_frame
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_center_on_hmd
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "center_on_hmd" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_center_on_hmd #-}

instance Method "center_on_hmd" GodotARVRServer
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_center_on_hmd (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_hmd_transform
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_hmd_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_hmd_transform #-}

instance Method "get_hmd_transform" GodotARVRServer
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_hmd_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_interface_count
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_interface_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_interface_count #-}

instance Method "get_interface_count" GodotARVRServer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_interface_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_interface
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_interface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_interface #-}

instance Method "get_interface" GodotARVRServer
           (Int -> IO GodotARVRInterface)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_interface (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_interfaces
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_interfaces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_interfaces #-}

instance Method "get_interfaces" GodotARVRServer (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_interfaces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_find_interface
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "find_interface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_find_interface #-}

instance Method "find_interface" GodotARVRServer
           (GodotString -> IO GodotARVRInterface)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_find_interface (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_tracker_count
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_tracker_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_tracker_count #-}

instance Method "get_tracker_count" GodotARVRServer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_tracker_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_tracker
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_tracker" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_tracker #-}

instance Method "get_tracker" GodotARVRServer
           (Int -> IO GodotARVRPositionalTracker)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_tracker (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_primary_interface
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_primary_interface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_primary_interface #-}

instance Method "get_primary_interface" GodotARVRServer
           (IO GodotARVRInterface)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_primary_interface
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_set_primary_interface
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "set_primary_interface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_set_primary_interface #-}

instance Method "set_primary_interface" GodotARVRServer
           (GodotARVRInterface -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_set_primary_interface
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_last_process_usec
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_last_process_usec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_last_process_usec #-}

instance Method "get_last_process_usec" GodotARVRServer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_last_process_usec
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_last_commit_usec
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_last_commit_usec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_last_commit_usec #-}

instance Method "get_last_commit_usec" GodotARVRServer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_last_commit_usec
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRServer_get_last_frame_usec
  = unsafePerformIO $
      withCString "ARVRServer" $
        \ clsNamePtr ->
          withCString "get_last_frame_usec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRServer_get_last_frame_usec #-}

instance Method "get_last_frame_usec" GodotARVRServer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRServer_get_last_frame_usec
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotExpression = GodotExpression GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotExpression where
        type BaseClass GodotExpression = GodotReference
        super = coerce
bindExpression_parse
  = unsafePerformIO $
      withCString "Expression" $
        \ clsNamePtr ->
          withCString "parse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindExpression_parse #-}

instance Method "parse" GodotExpression
           (GodotString -> GodotPoolStringArray -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindExpression_parse (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindExpression_execute
  = unsafePerformIO $
      withCString "Expression" $
        \ clsNamePtr ->
          withCString "execute" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindExpression_execute #-}

instance Method "execute" GodotExpression
           (GodotArray -> GodotObject -> Bool -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindExpression_execute (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindExpression_has_execute_failed
  = unsafePerformIO $
      withCString "Expression" $
        \ clsNamePtr ->
          withCString "has_execute_failed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindExpression_has_execute_failed #-}

instance Method "has_execute_failed" GodotExpression (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindExpression_has_execute_failed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindExpression_get_error_text
  = unsafePerformIO $
      withCString "Expression" $
        \ clsNamePtr ->
          withCString "get_error_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindExpression_get_error_text #-}

instance Method "get_error_text" GodotExpression (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindExpression_get_error_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsServer = GodotPhysicsServer GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotPhysicsServer where
        type BaseClass GodotPhysicsServer = GodotObject
        super = coerce
bindPhysicsServer_shape_create
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_shape_create #-}

instance Method "shape_create" GodotPhysicsServer
           (Int -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_shape_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_shape_set_data
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "shape_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_shape_set_data #-}

instance Method "shape_set_data" GodotPhysicsServer
           (GodotRid -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_shape_set_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_shape_get_type
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "shape_get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_shape_get_type #-}

instance Method "shape_get_type" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_shape_get_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_shape_get_data
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "shape_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_shape_get_data #-}

instance Method "shape_get_data" GodotPhysicsServer
           (GodotRid -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_shape_get_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_space_create
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "space_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_space_create #-}

instance Method "space_create" GodotPhysicsServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_space_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_space_set_active
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "space_set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_space_set_active #-}

instance Method "space_set_active" GodotPhysicsServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_space_set_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_space_is_active
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "space_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_space_is_active #-}

instance Method "space_is_active" GodotPhysicsServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_space_is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_space_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "space_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_space_set_param #-}

instance Method "space_set_param" GodotPhysicsServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_space_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_space_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "space_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_space_get_param #-}

instance Method "space_get_param" GodotPhysicsServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_space_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_space_get_direct_state
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "space_get_direct_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_space_get_direct_state #-}

instance Method "space_get_direct_state" GodotPhysicsServer
           (GodotRid -> IO GodotPhysicsDirectSpaceState)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_space_get_direct_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_create
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_create #-}

instance Method "area_create" GodotPhysicsServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_space
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_space #-}

instance Method "area_set_space" GodotPhysicsServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_space
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_space #-}

instance Method "area_get_space" GodotPhysicsServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_get_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_space_override_mode
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_space_override_mode #-}

instance Method "area_set_space_override_mode" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_area_set_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_space_override_mode
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_space_override_mode #-}

instance Method "area_get_space_override_mode" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_area_get_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_add_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_add_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_add_shape #-}

instance Method "area_add_shape" GodotPhysicsServer
           (GodotRid -> GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_add_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_shape #-}

instance Method "area_set_shape" GodotPhysicsServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_shape_transform
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_shape_transform #-}

instance Method "area_set_shape_transform" GodotPhysicsServer
           (GodotRid -> Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_shape_count
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_shape_count #-}

instance Method "area_get_shape_count" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_get_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_shape #-}

instance Method "area_get_shape" GodotPhysicsServer
           (GodotRid -> Int -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_get_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_shape_transform
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_shape_transform #-}

instance Method "area_get_shape_transform" GodotPhysicsServer
           (GodotRid -> Int -> IO GodotTransform)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_get_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_remove_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_remove_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_remove_shape #-}

instance Method "area_remove_shape" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_remove_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_clear_shapes
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_clear_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_clear_shapes #-}

instance Method "area_clear_shapes" GodotPhysicsServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_clear_shapes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_collision_layer
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_collision_layer #-}

instance Method "area_set_collision_layer" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_collision_mask
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_collision_mask #-}

instance Method "area_set_collision_mask" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_param #-}

instance Method "area_set_param" GodotPhysicsServer
           (GodotRid -> Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_transform
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_transform #-}

instance Method "area_set_transform" GodotPhysicsServer
           (GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_param #-}

instance Method "area_get_param" GodotPhysicsServer
           (GodotRid -> Int -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_transform
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_transform #-}

instance Method "area_get_transform" GodotPhysicsServer
           (GodotRid -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_attach_object_instance_id
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_attach_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_attach_object_instance_id #-}

instance Method "area_attach_object_instance_id" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_area_attach_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_get_object_instance_id
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_get_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_get_object_instance_id #-}

instance Method "area_get_object_instance_id" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_area_get_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_monitor_callback
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_monitor_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_monitor_callback #-}

instance Method "area_set_monitor_callback" GodotPhysicsServer
           (GodotRid -> GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_monitor_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_area_monitor_callback
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_area_monitor_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_area_monitor_callback #-}

instance Method "area_set_area_monitor_callback" GodotPhysicsServer
           (GodotRid -> GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_area_set_area_monitor_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_monitorable
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_monitorable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_monitorable #-}

instance Method "area_set_monitorable" GodotPhysicsServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_monitorable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_set_ray_pickable
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_set_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_set_ray_pickable #-}

instance Method "area_set_ray_pickable" GodotPhysicsServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_set_ray_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_area_is_ray_pickable
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "area_is_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_area_is_ray_pickable #-}

instance Method "area_is_ray_pickable" GodotPhysicsServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_area_is_ray_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_create
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_create #-}

instance Method "body_create" GodotPhysicsServer
           (Int -> Bool -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_space
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_space #-}

instance Method "body_set_space" GodotPhysicsServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_space
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_space #-}

instance Method "body_get_space" GodotPhysicsServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_mode
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_mode #-}

instance Method "body_set_mode" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_mode
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_mode #-}

instance Method "body_get_mode" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_collision_layer
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_collision_layer #-}

instance Method "body_set_collision_layer" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_collision_layer
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_collision_layer #-}

instance Method "body_get_collision_layer" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_collision_mask
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_collision_mask #-}

instance Method "body_set_collision_mask" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_collision_mask
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_collision_mask #-}

instance Method "body_get_collision_mask" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_add_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_add_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_add_shape #-}

instance Method "body_add_shape" GodotPhysicsServer
           (GodotRid -> GodotRid -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_add_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_shape #-}

instance Method "body_set_shape" GodotPhysicsServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_shape_transform
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_shape_transform #-}

instance Method "body_set_shape_transform" GodotPhysicsServer
           (GodotRid -> Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_shape_count
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_shape_count #-}

instance Method "body_get_shape_count" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_shape #-}

instance Method "body_get_shape" GodotPhysicsServer
           (GodotRid -> Int -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_shape_transform
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_shape_transform #-}

instance Method "body_get_shape_transform" GodotPhysicsServer
           (GodotRid -> Int -> IO GodotTransform)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_remove_shape
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_remove_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_remove_shape #-}

instance Method "body_remove_shape" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_remove_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_clear_shapes
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_clear_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_clear_shapes #-}

instance Method "body_clear_shapes" GodotPhysicsServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_clear_shapes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_attach_object_instance_id
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_attach_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_attach_object_instance_id #-}

instance Method "body_attach_object_instance_id" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_attach_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_object_instance_id
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_object_instance_id #-}

instance Method "body_get_object_instance_id" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_get_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_enable_continuous_collision_detection
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_enable_continuous_collision_detection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_enable_continuous_collision_detection
             #-}

instance Method "body_set_enable_continuous_collision_detection"
           GodotPhysicsServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_set_enable_continuous_collision_detection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_is_continuous_collision_detection_enabled
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_is_continuous_collision_detection_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_is_continuous_collision_detection_enabled
             #-}

instance Method "body_is_continuous_collision_detection_enabled"
           GodotPhysicsServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_is_continuous_collision_detection_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_param #-}

instance Method "body_set_param" GodotPhysicsServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_param #-}

instance Method "body_get_param" GodotPhysicsServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_kinematic_safe_margin
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_kinematic_safe_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_kinematic_safe_margin #-}

instance Method "body_set_kinematic_safe_margin" GodotPhysicsServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_set_kinematic_safe_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_kinematic_safe_margin
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_kinematic_safe_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_kinematic_safe_margin #-}

instance Method "body_get_kinematic_safe_margin" GodotPhysicsServer
           (GodotRid -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_get_kinematic_safe_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_state
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_state #-}

instance Method "body_set_state" GodotPhysicsServer
           (GodotRid -> Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_state
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_state #-}

instance Method "body_get_state" GodotPhysicsServer
           (GodotRid -> Int -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_add_central_force
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_add_central_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_add_central_force #-}

instance Method "body_add_central_force" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_add_central_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_add_force
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_add_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_add_force #-}

instance Method "body_add_force" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_add_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_add_torque
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_add_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_add_torque #-}

instance Method "body_add_torque" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_add_torque
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_apply_central_impulse
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_apply_central_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_apply_central_impulse #-}

instance Method "body_apply_central_impulse" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_apply_central_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_apply_impulse
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_apply_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_apply_impulse #-}

instance Method "body_apply_impulse" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_apply_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_apply_torque_impulse
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_apply_torque_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_apply_torque_impulse #-}

instance Method "body_apply_torque_impulse" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_apply_torque_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_axis_velocity
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_axis_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_axis_velocity #-}

instance Method "body_set_axis_velocity" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_axis_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_axis_lock
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_axis_lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_axis_lock #-}

instance Method "body_set_axis_lock" GodotPhysicsServer
           (GodotRid -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_axis_lock
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_is_axis_locked
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_is_axis_locked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_is_axis_locked #-}

instance Method "body_is_axis_locked" GodotPhysicsServer
           (GodotRid -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_is_axis_locked
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_add_collision_exception
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_add_collision_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_add_collision_exception #-}

instance Method "body_add_collision_exception" GodotPhysicsServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_add_collision_exception
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_remove_collision_exception
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_remove_collision_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_remove_collision_exception #-}

instance Method "body_remove_collision_exception"
           GodotPhysicsServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_remove_collision_exception
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_max_contacts_reported
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_max_contacts_reported #-}

instance Method "body_set_max_contacts_reported" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_set_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_max_contacts_reported
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_max_contacts_reported #-}

instance Method "body_get_max_contacts_reported" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_get_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_omit_force_integration
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_omit_force_integration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_omit_force_integration #-}

instance Method "body_set_omit_force_integration"
           GodotPhysicsServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_set_omit_force_integration
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_is_omitting_force_integration
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_is_omitting_force_integration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_is_omitting_force_integration
             #-}

instance Method "body_is_omitting_force_integration"
           GodotPhysicsServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_is_omitting_force_integration
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_force_integration_callback
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_force_integration_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_force_integration_callback
             #-}

instance Method "body_set_force_integration_callback"
           GodotPhysicsServer
           (GodotRid -> GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_body_set_force_integration_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_set_ray_pickable
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_set_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_set_ray_pickable #-}

instance Method "body_set_ray_pickable" GodotPhysicsServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_set_ray_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_is_ray_pickable
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_is_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_is_ray_pickable #-}

instance Method "body_is_ray_pickable" GodotPhysicsServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_is_ray_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_body_get_direct_state
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "body_get_direct_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_body_get_direct_state #-}

instance Method "body_get_direct_state" GodotPhysicsServer
           (GodotRid -> IO GodotPhysicsDirectBodyState)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_body_get_direct_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_create_pin
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_create_pin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_create_pin #-}

instance Method "joint_create_pin" GodotPhysicsServer
           (GodotRid ->
              GodotVector3 -> GodotRid -> GodotVector3 -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_create_pin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_pin_joint_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "pin_joint_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_pin_joint_set_param #-}

instance Method "pin_joint_set_param" GodotPhysicsServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_pin_joint_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_pin_joint_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "pin_joint_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_pin_joint_get_param #-}

instance Method "pin_joint_get_param" GodotPhysicsServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_pin_joint_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_pin_joint_set_local_a
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "pin_joint_set_local_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_pin_joint_set_local_a #-}

instance Method "pin_joint_set_local_a" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_pin_joint_set_local_a
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_pin_joint_get_local_a
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "pin_joint_get_local_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_pin_joint_get_local_a #-}

instance Method "pin_joint_get_local_a" GodotPhysicsServer
           (GodotRid -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_pin_joint_get_local_a
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_pin_joint_set_local_b
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "pin_joint_set_local_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_pin_joint_set_local_b #-}

instance Method "pin_joint_set_local_b" GodotPhysicsServer
           (GodotRid -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_pin_joint_set_local_b
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_pin_joint_get_local_b
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "pin_joint_get_local_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_pin_joint_get_local_b #-}

instance Method "pin_joint_get_local_b" GodotPhysicsServer
           (GodotRid -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_pin_joint_get_local_b
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_create_hinge
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_create_hinge" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_create_hinge #-}

instance Method "joint_create_hinge" GodotPhysicsServer
           (GodotRid ->
              GodotTransform -> GodotRid -> GodotTransform -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_create_hinge
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_hinge_joint_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "hinge_joint_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_hinge_joint_set_param #-}

instance Method "hinge_joint_set_param" GodotPhysicsServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_hinge_joint_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_hinge_joint_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "hinge_joint_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_hinge_joint_get_param #-}

instance Method "hinge_joint_get_param" GodotPhysicsServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_hinge_joint_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_hinge_joint_set_flag
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "hinge_joint_set_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_hinge_joint_set_flag #-}

instance Method "hinge_joint_set_flag" GodotPhysicsServer
           (GodotRid -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_hinge_joint_set_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_hinge_joint_get_flag
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "hinge_joint_get_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_hinge_joint_get_flag #-}

instance Method "hinge_joint_get_flag" GodotPhysicsServer
           (GodotRid -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_hinge_joint_get_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_create_slider
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_create_slider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_create_slider #-}

instance Method "joint_create_slider" GodotPhysicsServer
           (GodotRid ->
              GodotTransform -> GodotRid -> GodotTransform -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_create_slider
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_slider_joint_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "slider_joint_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_slider_joint_set_param #-}

instance Method "slider_joint_set_param" GodotPhysicsServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_slider_joint_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_slider_joint_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "slider_joint_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_slider_joint_get_param #-}

instance Method "slider_joint_get_param" GodotPhysicsServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_slider_joint_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_create_cone_twist
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_create_cone_twist" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_create_cone_twist #-}

instance Method "joint_create_cone_twist" GodotPhysicsServer
           (GodotRid ->
              GodotTransform -> GodotRid -> GodotTransform -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_create_cone_twist
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_cone_twist_joint_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "cone_twist_joint_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_cone_twist_joint_set_param #-}

instance Method "cone_twist_joint_set_param" GodotPhysicsServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_cone_twist_joint_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_cone_twist_joint_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "cone_twist_joint_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_cone_twist_joint_get_param #-}

instance Method "cone_twist_joint_get_param" GodotPhysicsServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_cone_twist_joint_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_get_type
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_get_type #-}

instance Method "joint_get_type" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_get_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_set_solver_priority
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_set_solver_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_set_solver_priority #-}

instance Method "joint_set_solver_priority" GodotPhysicsServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_set_solver_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_get_solver_priority
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_get_solver_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_get_solver_priority #-}

instance Method "joint_get_solver_priority" GodotPhysicsServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_get_solver_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_joint_create_generic_6dof
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "joint_create_generic_6dof" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_joint_create_generic_6dof #-}

instance Method "joint_create_generic_6dof" GodotPhysicsServer
           (GodotRid ->
              GodotTransform -> GodotRid -> GodotTransform -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_joint_create_generic_6dof
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_generic_6dof_joint_set_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "generic_6dof_joint_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_generic_6dof_joint_set_param #-}

instance Method "generic_6dof_joint_set_param" GodotPhysicsServer
           (GodotRid -> Int -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_generic_6dof_joint_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_generic_6dof_joint_get_param
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "generic_6dof_joint_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_generic_6dof_joint_get_param #-}

instance Method "generic_6dof_joint_get_param" GodotPhysicsServer
           (GodotRid -> Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_generic_6dof_joint_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_generic_6dof_joint_set_flag
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "generic_6dof_joint_set_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_generic_6dof_joint_set_flag #-}

instance Method "generic_6dof_joint_set_flag" GodotPhysicsServer
           (GodotRid -> Int -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_generic_6dof_joint_set_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_generic_6dof_joint_get_flag
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "generic_6dof_joint_get_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_generic_6dof_joint_get_flag #-}

instance Method "generic_6dof_joint_get_flag" GodotPhysicsServer
           (GodotRid -> Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsServer_generic_6dof_joint_get_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_free_rid
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "free_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_free_rid #-}

instance Method "free_rid" GodotPhysicsServer (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_free_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_set_active
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_set_active #-}

instance Method "set_active" GodotPhysicsServer (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_set_active (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsServer_get_process_info
  = unsafePerformIO $
      withCString "PhysicsServer" $
        \ clsNamePtr ->
          withCString "get_process_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsServer_get_process_info #-}

instance Method "get_process_info" GodotPhysicsServer
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsServer_get_process_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysics2DServer = GodotPhysics2DServer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DServer where
        type BaseClass GodotPhysics2DServer = GodotObject
        super = coerce
bindPhysics2DServer_line_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "line_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_line_shape_create #-}

instance Method "line_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_line_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_ray_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "ray_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_ray_shape_create #-}

instance Method "ray_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_ray_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_segment_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "segment_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_segment_shape_create #-}

instance Method "segment_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_segment_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_circle_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "circle_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_circle_shape_create #-}

instance Method "circle_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_circle_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_rectangle_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "rectangle_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_rectangle_shape_create #-}

instance Method "rectangle_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_rectangle_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_capsule_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "capsule_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_capsule_shape_create #-}

instance Method "capsule_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_capsule_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_convex_polygon_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "convex_polygon_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_convex_polygon_shape_create #-}

instance Method "convex_polygon_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_convex_polygon_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_concave_polygon_shape_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "concave_polygon_shape_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_concave_polygon_shape_create #-}

instance Method "concave_polygon_shape_create" GodotPhysics2DServer
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_concave_polygon_shape_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_shape_set_data
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "shape_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_shape_set_data #-}

instance Method "shape_set_data" GodotPhysics2DServer
           (GodotRid -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_shape_set_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_shape_get_type
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "shape_get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_shape_get_type #-}

instance Method "shape_get_type" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_shape_get_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_shape_get_data
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "shape_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_shape_get_data #-}

instance Method "shape_get_data" GodotPhysics2DServer
           (GodotRid -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_shape_get_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_space_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "space_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_space_create #-}

instance Method "space_create" GodotPhysics2DServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_space_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_space_set_active
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "space_set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_space_set_active #-}

instance Method "space_set_active" GodotPhysics2DServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_space_set_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_space_is_active
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "space_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_space_is_active #-}

instance Method "space_is_active" GodotPhysics2DServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_space_is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_space_set_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "space_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_space_set_param #-}

instance Method "space_set_param" GodotPhysics2DServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_space_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_space_get_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "space_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_space_get_param #-}

instance Method "space_get_param" GodotPhysics2DServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_space_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_space_get_direct_state
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "space_get_direct_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_space_get_direct_state #-}

instance Method "space_get_direct_state" GodotPhysics2DServer
           (GodotRid -> IO GodotPhysics2DDirectSpaceState)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_space_get_direct_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_create #-}

instance Method "area_create" GodotPhysics2DServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_space
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_space #-}

instance Method "area_set_space" GodotPhysics2DServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_space
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_space #-}

instance Method "area_get_space" GodotPhysics2DServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_get_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_space_override_mode
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_space_override_mode #-}

instance Method "area_set_space_override_mode" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_area_set_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_space_override_mode
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_space_override_mode #-}

instance Method "area_get_space_override_mode" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_area_get_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_add_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_add_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_add_shape #-}

instance Method "area_add_shape" GodotPhysics2DServer
           (GodotRid -> GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_add_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_shape #-}

instance Method "area_set_shape" GodotPhysics2DServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_shape_transform
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_shape_transform #-}

instance Method "area_set_shape_transform" GodotPhysics2DServer
           (GodotRid -> Int -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_shape_disabled
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_shape_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_shape_disabled #-}

instance Method "area_set_shape_disabled" GodotPhysics2DServer
           (GodotRid -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_shape_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_shape_count
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_shape_count #-}

instance Method "area_get_shape_count" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_get_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_shape #-}

instance Method "area_get_shape" GodotPhysics2DServer
           (GodotRid -> Int -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_get_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_shape_transform
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_shape_transform #-}

instance Method "area_get_shape_transform" GodotPhysics2DServer
           (GodotRid -> Int -> IO GodotTransform2d)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_get_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_remove_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_remove_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_remove_shape #-}

instance Method "area_remove_shape" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_remove_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_clear_shapes
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_clear_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_clear_shapes #-}

instance Method "area_clear_shapes" GodotPhysics2DServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_clear_shapes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_collision_layer
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_collision_layer #-}

instance Method "area_set_collision_layer" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_collision_mask
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_collision_mask #-}

instance Method "area_set_collision_mask" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_param #-}

instance Method "area_set_param" GodotPhysics2DServer
           (GodotRid -> Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_transform
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_transform #-}

instance Method "area_set_transform" GodotPhysics2DServer
           (GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_param #-}

instance Method "area_get_param" GodotPhysics2DServer
           (GodotRid -> Int -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_transform
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_transform #-}

instance Method "area_get_transform" GodotPhysics2DServer
           (GodotRid -> IO GodotTransform2d)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_attach_object_instance_id
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_attach_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_attach_object_instance_id #-}

instance Method "area_attach_object_instance_id"
           GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_area_attach_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_get_object_instance_id
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_get_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_get_object_instance_id #-}

instance Method "area_get_object_instance_id" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_area_get_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_monitor_callback
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_monitor_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_monitor_callback #-}

instance Method "area_set_monitor_callback" GodotPhysics2DServer
           (GodotRid -> GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_area_set_monitor_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_area_monitor_callback
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_area_monitor_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_area_monitor_callback #-}

instance Method "area_set_area_monitor_callback"
           GodotPhysics2DServer
           (GodotRid -> GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_area_set_area_monitor_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_area_set_monitorable
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "area_set_monitorable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_area_set_monitorable #-}

instance Method "area_set_monitorable" GodotPhysics2DServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_area_set_monitorable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_create #-}

instance Method "body_create" GodotPhysics2DServer (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_space
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_space #-}

instance Method "body_set_space" GodotPhysics2DServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_space
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_space #-}

instance Method "body_get_space" GodotPhysics2DServer
           (GodotRid -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_mode
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_mode #-}

instance Method "body_set_mode" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_mode
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_mode #-}

instance Method "body_get_mode" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_add_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_add_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_add_shape #-}

instance Method "body_add_shape" GodotPhysics2DServer
           (GodotRid -> GodotRid -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_add_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_shape #-}

instance Method "body_set_shape" GodotPhysics2DServer
           (GodotRid -> Int -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_shape_transform
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_shape_transform #-}

instance Method "body_set_shape_transform" GodotPhysics2DServer
           (GodotRid -> Int -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_shape_metadata
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_shape_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_shape_metadata #-}

instance Method "body_set_shape_metadata" GodotPhysics2DServer
           (GodotRid -> Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_shape_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_shape_count
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_shape_count #-}

instance Method "body_get_shape_count" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_shape #-}

instance Method "body_get_shape" GodotPhysics2DServer
           (GodotRid -> Int -> IO GodotRid)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_shape_transform
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_shape_transform #-}

instance Method "body_get_shape_transform" GodotPhysics2DServer
           (GodotRid -> Int -> IO GodotTransform2d)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_shape_metadata
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_shape_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_shape_metadata #-}

instance Method "body_get_shape_metadata" GodotPhysics2DServer
           (GodotRid -> Int -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_shape_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_remove_shape
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_remove_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_remove_shape #-}

instance Method "body_remove_shape" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_remove_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_clear_shapes
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_clear_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_clear_shapes #-}

instance Method "body_clear_shapes" GodotPhysics2DServer
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_clear_shapes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_shape_disabled
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_shape_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_shape_disabled #-}

instance Method "body_set_shape_disabled" GodotPhysics2DServer
           (GodotRid -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_shape_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_shape_as_one_way_collision
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_shape_as_one_way_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_shape_as_one_way_collision
             #-}

instance Method "body_set_shape_as_one_way_collision"
           GodotPhysics2DServer
           (GodotRid -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_set_shape_as_one_way_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_attach_object_instance_id
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_attach_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_attach_object_instance_id #-}

instance Method "body_attach_object_instance_id"
           GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_attach_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_object_instance_id
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_object_instance_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_object_instance_id #-}

instance Method "body_get_object_instance_id" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_get_object_instance_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_continuous_collision_detection_mode
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_continuous_collision_detection_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_continuous_collision_detection_mode
             #-}

instance Method "body_set_continuous_collision_detection_mode"
           GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_set_continuous_collision_detection_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_continuous_collision_detection_mode
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_continuous_collision_detection_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_continuous_collision_detection_mode
             #-}

instance Method "body_get_continuous_collision_detection_mode"
           GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_get_continuous_collision_detection_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_collision_layer
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_collision_layer #-}

instance Method "body_set_collision_layer" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_collision_layer
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_collision_layer #-}

instance Method "body_get_collision_layer" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_collision_mask
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_collision_mask #-}

instance Method "body_set_collision_mask" GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_collision_mask
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_collision_mask #-}

instance Method "body_get_collision_mask" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_param #-}

instance Method "body_set_param" GodotPhysics2DServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_param #-}

instance Method "body_get_param" GodotPhysics2DServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_state
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_state #-}

instance Method "body_set_state" GodotPhysics2DServer
           (GodotRid -> Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_state
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_state #-}

instance Method "body_get_state" GodotPhysics2DServer
           (GodotRid -> Int -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_apply_central_impulse
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_apply_central_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_apply_central_impulse #-}

instance Method "body_apply_central_impulse" GodotPhysics2DServer
           (GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_apply_central_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_apply_torque_impulse
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_apply_torque_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_apply_torque_impulse #-}

instance Method "body_apply_torque_impulse" GodotPhysics2DServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_apply_torque_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_apply_impulse
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_apply_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_apply_impulse #-}

instance Method "body_apply_impulse" GodotPhysics2DServer
           (GodotRid -> GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_apply_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_add_central_force
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_add_central_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_add_central_force #-}

instance Method "body_add_central_force" GodotPhysics2DServer
           (GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_add_central_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_add_force
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_add_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_add_force #-}

instance Method "body_add_force" GodotPhysics2DServer
           (GodotRid -> GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_add_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_add_torque
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_add_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_add_torque #-}

instance Method "body_add_torque" GodotPhysics2DServer
           (GodotRid -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_add_torque
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_axis_velocity
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_axis_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_axis_velocity #-}

instance Method "body_set_axis_velocity" GodotPhysics2DServer
           (GodotRid -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_set_axis_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_add_collision_exception
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_add_collision_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_add_collision_exception #-}

instance Method "body_add_collision_exception" GodotPhysics2DServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_add_collision_exception
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_remove_collision_exception
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_remove_collision_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_remove_collision_exception
             #-}

instance Method "body_remove_collision_exception"
           GodotPhysics2DServer
           (GodotRid -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_remove_collision_exception
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_max_contacts_reported
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_max_contacts_reported #-}

instance Method "body_set_max_contacts_reported"
           GodotPhysics2DServer
           (GodotRid -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_set_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_max_contacts_reported
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_max_contacts_reported #-}

instance Method "body_get_max_contacts_reported"
           GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_get_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_omit_force_integration
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_omit_force_integration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_omit_force_integration
             #-}

instance Method "body_set_omit_force_integration"
           GodotPhysics2DServer
           (GodotRid -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_set_omit_force_integration
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_is_omitting_force_integration
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_is_omitting_force_integration" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_is_omitting_force_integration
             #-}

instance Method "body_is_omitting_force_integration"
           GodotPhysics2DServer
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_is_omitting_force_integration
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_set_force_integration_callback
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_set_force_integration_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_set_force_integration_callback
             #-}

instance Method "body_set_force_integration_callback"
           GodotPhysics2DServer
           (GodotRid -> GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_body_set_force_integration_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_test_motion
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_test_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_test_motion #-}

instance Method "body_test_motion" GodotPhysics2DServer
           (GodotRid ->
              GodotTransform2d ->
                GodotVector2 ->
                  Bool -> Float -> GodotPhysics2DTestMotionResult -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_test_motion
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_body_get_direct_state
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "body_get_direct_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_body_get_direct_state #-}

instance Method "body_get_direct_state" GodotPhysics2DServer
           (GodotRid -> IO GodotPhysics2DDirectBodyState)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_body_get_direct_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_joint_set_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "joint_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_joint_set_param #-}

instance Method "joint_set_param" GodotPhysics2DServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_joint_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_joint_get_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "joint_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_joint_get_param #-}

instance Method "joint_get_param" GodotPhysics2DServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_joint_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_pin_joint_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "pin_joint_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_pin_joint_create #-}

instance Method "pin_joint_create" GodotPhysics2DServer
           (GodotVector2 -> GodotRid -> GodotRid -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_pin_joint_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_groove_joint_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "groove_joint_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_groove_joint_create #-}

instance Method "groove_joint_create" GodotPhysics2DServer
           (GodotVector2 ->
              GodotVector2 ->
                GodotVector2 -> GodotRid -> GodotRid -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_groove_joint_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_damped_spring_joint_create
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "damped_spring_joint_create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_damped_spring_joint_create #-}

instance Method "damped_spring_joint_create" GodotPhysics2DServer
           (GodotVector2 ->
              GodotVector2 -> GodotRid -> GodotRid -> IO GodotRid)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_damped_spring_joint_create
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_damped_string_joint_set_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "damped_string_joint_set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_damped_string_joint_set_param #-}

instance Method "damped_string_joint_set_param"
           GodotPhysics2DServer
           (GodotRid -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_damped_string_joint_set_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_damped_string_joint_get_param
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "damped_string_joint_get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_damped_string_joint_get_param #-}

instance Method "damped_string_joint_get_param"
           GodotPhysics2DServer
           (GodotRid -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DServer_damped_string_joint_get_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_joint_get_type
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "joint_get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_joint_get_type #-}

instance Method "joint_get_type" GodotPhysics2DServer
           (GodotRid -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_joint_get_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_free_rid
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "free_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_free_rid #-}

instance Method "free_rid" GodotPhysics2DServer (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_free_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_set_active
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_set_active #-}

instance Method "set_active" GodotPhysics2DServer (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_set_active (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DServer_get_process_info
  = unsafePerformIO $
      withCString "Physics2DServer" $
        \ clsNamePtr ->
          withCString "get_process_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DServer_get_process_info #-}

instance Method "get_process_info" GodotPhysics2DServer
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DServer_get_process_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotARVRInterface = GodotARVRInterface GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotARVRInterface where
        type BaseClass GodotARVRInterface = GodotReference
        super = coerce
bindARVRInterface_get_name
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_get_name #-}

instance Method "get_name" GodotARVRInterface (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_get_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_get_capabilities
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "get_capabilities" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_get_capabilities #-}

instance Method "get_capabilities" GodotARVRInterface (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_get_capabilities
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_is_primary
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "is_primary" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_is_primary #-}

instance Method "is_primary" GodotARVRInterface (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_is_primary (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_set_is_primary
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "set_is_primary" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_set_is_primary #-}

instance Method "set_is_primary" GodotARVRInterface (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_set_is_primary
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_is_initialized
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "is_initialized" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_is_initialized #-}

instance Method "is_initialized" GodotARVRInterface (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_is_initialized
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_set_is_initialized
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "set_is_initialized" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_set_is_initialized #-}

instance Method "set_is_initialized" GodotARVRInterface
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_set_is_initialized
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_initialize
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "initialize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_initialize #-}

instance Method "initialize" GodotARVRInterface (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_initialize (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_uninitialize
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "uninitialize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_uninitialize #-}

instance Method "uninitialize" GodotARVRInterface (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_uninitialize (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_get_tracking_status
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "get_tracking_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_get_tracking_status #-}

instance Method "get_tracking_status" GodotARVRInterface (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_get_tracking_status
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_get_render_targetsize
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "get_render_targetsize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_get_render_targetsize #-}

instance Method "get_render_targetsize" GodotARVRInterface
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_get_render_targetsize
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_is_stereo
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "is_stereo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_is_stereo #-}

instance Method "is_stereo" GodotARVRInterface (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRInterface_is_stereo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_get_anchor_detection_is_enabled
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "get_anchor_detection_is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_get_anchor_detection_is_enabled #-}

instance Method "get_anchor_detection_is_enabled"
           GodotARVRInterface
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindARVRInterface_get_anchor_detection_is_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRInterface_set_anchor_detection_is_enabled
  = unsafePerformIO $
      withCString "ARVRInterface" $
        \ clsNamePtr ->
          withCString "set_anchor_detection_is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRInterface_set_anchor_detection_is_enabled #-}

instance Method "set_anchor_detection_is_enabled"
           GodotARVRInterface
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindARVRInterface_set_anchor_detection_is_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotARVRPositionalTracker = GodotARVRPositionalTracker GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotARVRPositionalTracker where
        type BaseClass GodotARVRPositionalTracker = GodotObject
        super = coerce
bindARVRPositionalTracker_get_type
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_type #-}

instance Method "get_type" GodotARVRPositionalTracker (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_name
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_name #-}

instance Method "get_name" GodotARVRPositionalTracker
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_joy_id
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_joy_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_joy_id #-}

instance Method "get_joy_id" GodotARVRPositionalTracker (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_joy_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_tracks_orientation
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_tracks_orientation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_tracks_orientation #-}

instance Method "get_tracks_orientation" GodotARVRPositionalTracker
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindARVRPositionalTracker_get_tracks_orientation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_orientation
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_orientation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_orientation #-}

instance Method "get_orientation" GodotARVRPositionalTracker
           (IO GodotBasis)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_orientation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_tracks_position
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_tracks_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_tracks_position #-}

instance Method "get_tracks_position" GodotARVRPositionalTracker
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindARVRPositionalTracker_get_tracks_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_position
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_position #-}

instance Method "get_position" GodotARVRPositionalTracker
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_hand
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_hand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_hand #-}

instance Method "get_hand" GodotARVRPositionalTracker (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_hand
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_transform
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_transform #-}

instance Method "get_transform" GodotARVRPositionalTracker
           (Bool -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker__set_type
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "_set_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker__set_type #-}

instance Method "_set_type" GodotARVRPositionalTracker
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker__set_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker__set_name
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "_set_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker__set_name #-}

instance Method "_set_name" GodotARVRPositionalTracker
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker__set_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker__set_joy_id
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "_set_joy_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker__set_joy_id #-}

instance Method "_set_joy_id" GodotARVRPositionalTracker
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker__set_joy_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker__set_orientation
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "_set_orientation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker__set_orientation #-}

instance Method "_set_orientation" GodotARVRPositionalTracker
           (GodotBasis -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker__set_orientation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker__set_rw_position
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "_set_rw_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker__set_rw_position #-}

instance Method "_set_rw_position" GodotARVRPositionalTracker
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker__set_rw_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_get_rumble
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "get_rumble" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_get_rumble #-}

instance Method "get_rumble" GodotARVRPositionalTracker (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_get_rumble
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRPositionalTracker_set_rumble
  = unsafePerformIO $
      withCString "ARVRPositionalTracker" $
        \ clsNamePtr ->
          withCString "set_rumble" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRPositionalTracker_set_rumble #-}

instance Method "set_rumble" GodotARVRPositionalTracker
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRPositionalTracker_set_rumble
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioStream = GodotAudioStream GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotAudioStream where
        type BaseClass GodotAudioStream = GodotResource
        super = coerce
bindAudioStream_get_length
  = unsafePerformIO $
      withCString "AudioStream" $
        \ clsNamePtr ->
          withCString "get_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStream_get_length #-}

instance Method "get_length" GodotAudioStream (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStream_get_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioStreamPlayback = GodotAudioStreamPlayback GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamPlayback where
        type BaseClass GodotAudioStreamPlayback = GodotReference
        super = coerce

newtype GodotAudioStreamMicrophone = GodotAudioStreamMicrophone GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamMicrophone where
        type BaseClass GodotAudioStreamMicrophone = GodotAudioStream
        super = coerce

newtype GodotAudioStreamRandomPitch = GodotAudioStreamRandomPitch GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamRandomPitch where
        type BaseClass GodotAudioStreamRandomPitch = GodotAudioStream
        super = coerce
bindAudioStreamRandomPitch_set_audio_stream
  = unsafePerformIO $
      withCString "AudioStreamRandomPitch" $
        \ clsNamePtr ->
          withCString "set_audio_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamRandomPitch_set_audio_stream #-}

instance Method "set_audio_stream" GodotAudioStreamRandomPitch
           (GodotAudioStream -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamRandomPitch_set_audio_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamRandomPitch_get_audio_stream
  = unsafePerformIO $
      withCString "AudioStreamRandomPitch" $
        \ clsNamePtr ->
          withCString "get_audio_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamRandomPitch_get_audio_stream #-}

instance Method "get_audio_stream" GodotAudioStreamRandomPitch
           (IO GodotAudioStream)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamRandomPitch_get_audio_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamRandomPitch_set_random_pitch
  = unsafePerformIO $
      withCString "AudioStreamRandomPitch" $
        \ clsNamePtr ->
          withCString "set_random_pitch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamRandomPitch_set_random_pitch #-}

instance Method "set_random_pitch" GodotAudioStreamRandomPitch
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamRandomPitch_set_random_pitch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamRandomPitch_get_random_pitch
  = unsafePerformIO $
      withCString "AudioStreamRandomPitch" $
        \ clsNamePtr ->
          withCString "get_random_pitch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamRandomPitch_get_random_pitch #-}

instance Method "get_random_pitch" GodotAudioStreamRandomPitch
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamRandomPitch_get_random_pitch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffect = GodotAudioEffect GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotAudioEffect where
        type BaseClass GodotAudioEffect = GodotResource
        super = coerce

newtype GodotAudioEffectEQ = GodotAudioEffectEQ GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectEQ where
        type BaseClass GodotAudioEffectEQ = GodotAudioEffect
        super = coerce
bindAudioEffectEQ_set_band_gain_db
  = unsafePerformIO $
      withCString "AudioEffectEQ" $
        \ clsNamePtr ->
          withCString "set_band_gain_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectEQ_set_band_gain_db #-}

instance Method "set_band_gain_db" GodotAudioEffectEQ
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectEQ_set_band_gain_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectEQ_get_band_gain_db
  = unsafePerformIO $
      withCString "AudioEffectEQ" $
        \ clsNamePtr ->
          withCString "get_band_gain_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectEQ_get_band_gain_db #-}

instance Method "get_band_gain_db" GodotAudioEffectEQ
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectEQ_get_band_gain_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectEQ_get_band_count
  = unsafePerformIO $
      withCString "AudioEffectEQ" $
        \ clsNamePtr ->
          withCString "get_band_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectEQ_get_band_count #-}

instance Method "get_band_count" GodotAudioEffectEQ (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectEQ_get_band_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectFilter = GodotAudioEffectFilter GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectFilter where
        type BaseClass GodotAudioEffectFilter = GodotAudioEffect
        super = coerce
bindAudioEffectFilter_set_cutoff
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "set_cutoff" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_set_cutoff #-}

instance Method "set_cutoff" GodotAudioEffectFilter
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_set_cutoff
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectFilter_get_cutoff
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "get_cutoff" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_get_cutoff #-}

instance Method "get_cutoff" GodotAudioEffectFilter (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_get_cutoff
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectFilter_set_resonance
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "set_resonance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_set_resonance #-}

instance Method "set_resonance" GodotAudioEffectFilter
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_set_resonance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectFilter_get_resonance
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "get_resonance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_get_resonance #-}

instance Method "get_resonance" GodotAudioEffectFilter (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_get_resonance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectFilter_set_gain
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "set_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_set_gain #-}

instance Method "set_gain" GodotAudioEffectFilter (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_set_gain (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectFilter_get_gain
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "get_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_get_gain #-}

instance Method "get_gain" GodotAudioEffectFilter (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_get_gain (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectFilter_set_db
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "set_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_set_db #-}

instance Method "set_db" GodotAudioEffectFilter (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_set_db (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectFilter_get_db
  = unsafePerformIO $
      withCString "AudioEffectFilter" $
        \ clsNamePtr ->
          withCString "get_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectFilter_get_db #-}

instance Method "get_db" GodotAudioEffectFilter (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectFilter_get_db (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioBusLayout = GodotAudioBusLayout GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotAudioBusLayout where
        type BaseClass GodotAudioBusLayout = GodotResource
        super = coerce

newtype GodotAudioEffectAmplify = GodotAudioEffectAmplify GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectAmplify where
        type BaseClass GodotAudioEffectAmplify = GodotAudioEffect
        super = coerce
bindAudioEffectAmplify_set_volume_db
  = unsafePerformIO $
      withCString "AudioEffectAmplify" $
        \ clsNamePtr ->
          withCString "set_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectAmplify_set_volume_db #-}

instance Method "set_volume_db" GodotAudioEffectAmplify
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectAmplify_set_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectAmplify_get_volume_db
  = unsafePerformIO $
      withCString "AudioEffectAmplify" $
        \ clsNamePtr ->
          withCString "get_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectAmplify_get_volume_db #-}

instance Method "get_volume_db" GodotAudioEffectAmplify (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectAmplify_get_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectReverb = GodotAudioEffectReverb GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectReverb where
        type BaseClass GodotAudioEffectReverb = GodotAudioEffect
        super = coerce
bindAudioEffectReverb_set_predelay_msec
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_predelay_msec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_predelay_msec #-}

instance Method "set_predelay_msec" GodotAudioEffectReverb
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_predelay_msec
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_predelay_msec
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_predelay_msec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_predelay_msec #-}

instance Method "get_predelay_msec" GodotAudioEffectReverb
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_predelay_msec
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_set_predelay_feedback
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_predelay_feedback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_predelay_feedback #-}

instance Method "set_predelay_feedback" GodotAudioEffectReverb
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_predelay_feedback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_predelay_feedback
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_predelay_feedback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_predelay_feedback #-}

instance Method "get_predelay_feedback" GodotAudioEffectReverb
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_predelay_feedback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_set_room_size
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_room_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_room_size #-}

instance Method "set_room_size" GodotAudioEffectReverb
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_room_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_room_size
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_room_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_room_size #-}

instance Method "get_room_size" GodotAudioEffectReverb (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_room_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_set_damping
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_damping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_damping #-}

instance Method "set_damping" GodotAudioEffectReverb
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_damping
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_damping
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_damping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_damping #-}

instance Method "get_damping" GodotAudioEffectReverb (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_damping
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_set_spread
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_spread #-}

instance Method "set_spread" GodotAudioEffectReverb
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_spread
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_spread
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_spread #-}

instance Method "get_spread" GodotAudioEffectReverb (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_spread
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_set_dry
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_dry" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_dry #-}

instance Method "set_dry" GodotAudioEffectReverb (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_dry (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_dry
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_dry" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_dry #-}

instance Method "get_dry" GodotAudioEffectReverb (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_dry (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_set_wet
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_wet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_wet #-}

instance Method "set_wet" GodotAudioEffectReverb (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_wet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_wet
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_wet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_wet #-}

instance Method "get_wet" GodotAudioEffectReverb (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_wet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_set_hpf
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "set_hpf" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_set_hpf #-}

instance Method "set_hpf" GodotAudioEffectReverb (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_set_hpf (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectReverb_get_hpf
  = unsafePerformIO $
      withCString "AudioEffectReverb" $
        \ clsNamePtr ->
          withCString "get_hpf" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectReverb_get_hpf #-}

instance Method "get_hpf" GodotAudioEffectReverb (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectReverb_get_hpf (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectLowPassFilter = GodotAudioEffectLowPassFilter GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectLowPassFilter where
        type BaseClass GodotAudioEffectLowPassFilter =
             GodotAudioEffectFilter
        super = coerce

newtype GodotAudioEffectHighPassFilter = GodotAudioEffectHighPassFilter GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectHighPassFilter where
        type BaseClass GodotAudioEffectHighPassFilter =
             GodotAudioEffectFilter
        super = coerce

newtype GodotAudioEffectBandPassFilter = GodotAudioEffectBandPassFilter GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectBandPassFilter where
        type BaseClass GodotAudioEffectBandPassFilter =
             GodotAudioEffectFilter
        super = coerce

newtype GodotAudioEffectNotchFilter = GodotAudioEffectNotchFilter GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectNotchFilter where
        type BaseClass GodotAudioEffectNotchFilter = GodotAudioEffectFilter
        super = coerce

newtype GodotAudioEffectBandLimitFilter = GodotAudioEffectBandLimitFilter GodotObject
                                            deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectBandLimitFilter where
        type BaseClass GodotAudioEffectBandLimitFilter =
             GodotAudioEffectFilter
        super = coerce

newtype GodotAudioEffectLowShelfFilter = GodotAudioEffectLowShelfFilter GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectLowShelfFilter where
        type BaseClass GodotAudioEffectLowShelfFilter =
             GodotAudioEffectFilter
        super = coerce

newtype GodotAudioEffectHighShelfFilter = GodotAudioEffectHighShelfFilter GodotObject
                                            deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectHighShelfFilter where
        type BaseClass GodotAudioEffectHighShelfFilter =
             GodotAudioEffectFilter
        super = coerce

newtype GodotAudioEffectEQ6 = GodotAudioEffectEQ6 GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectEQ6 where
        type BaseClass GodotAudioEffectEQ6 = GodotAudioEffectEQ
        super = coerce

newtype GodotAudioEffectEQ10 = GodotAudioEffectEQ10 GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectEQ10 where
        type BaseClass GodotAudioEffectEQ10 = GodotAudioEffectEQ
        super = coerce

newtype GodotAudioEffectEQ21 = GodotAudioEffectEQ21 GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectEQ21 where
        type BaseClass GodotAudioEffectEQ21 = GodotAudioEffectEQ
        super = coerce

newtype GodotAudioEffectDistortion = GodotAudioEffectDistortion GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectDistortion where
        type BaseClass GodotAudioEffectDistortion = GodotAudioEffect
        super = coerce
bindAudioEffectDistortion_set_mode
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_set_mode #-}

instance Method "set_mode" GodotAudioEffectDistortion
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_set_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_get_mode
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_get_mode #-}

instance Method "get_mode" GodotAudioEffectDistortion (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_get_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_set_pre_gain
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "set_pre_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_set_pre_gain #-}

instance Method "set_pre_gain" GodotAudioEffectDistortion
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_set_pre_gain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_get_pre_gain
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "get_pre_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_get_pre_gain #-}

instance Method "get_pre_gain" GodotAudioEffectDistortion
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_get_pre_gain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_set_keep_hf_hz
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "set_keep_hf_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_set_keep_hf_hz #-}

instance Method "set_keep_hf_hz" GodotAudioEffectDistortion
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_set_keep_hf_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_get_keep_hf_hz
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "get_keep_hf_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_get_keep_hf_hz #-}

instance Method "get_keep_hf_hz" GodotAudioEffectDistortion
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_get_keep_hf_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_set_drive
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "set_drive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_set_drive #-}

instance Method "set_drive" GodotAudioEffectDistortion
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_set_drive
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_get_drive
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "get_drive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_get_drive #-}

instance Method "get_drive" GodotAudioEffectDistortion (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_get_drive
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_set_post_gain
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "set_post_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_set_post_gain #-}

instance Method "set_post_gain" GodotAudioEffectDistortion
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_set_post_gain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDistortion_get_post_gain
  = unsafePerformIO $
      withCString "AudioEffectDistortion" $
        \ clsNamePtr ->
          withCString "get_post_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDistortion_get_post_gain #-}

instance Method "get_post_gain" GodotAudioEffectDistortion
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDistortion_get_post_gain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectStereoEnhance = GodotAudioEffectStereoEnhance GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectStereoEnhance where
        type BaseClass GodotAudioEffectStereoEnhance = GodotAudioEffect
        super = coerce
bindAudioEffectStereoEnhance_set_pan_pullout
  = unsafePerformIO $
      withCString "AudioEffectStereoEnhance" $
        \ clsNamePtr ->
          withCString "set_pan_pullout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectStereoEnhance_set_pan_pullout #-}

instance Method "set_pan_pullout" GodotAudioEffectStereoEnhance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectStereoEnhance_set_pan_pullout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectStereoEnhance_get_pan_pullout
  = unsafePerformIO $
      withCString "AudioEffectStereoEnhance" $
        \ clsNamePtr ->
          withCString "get_pan_pullout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectStereoEnhance_get_pan_pullout #-}

instance Method "get_pan_pullout" GodotAudioEffectStereoEnhance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectStereoEnhance_get_pan_pullout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectStereoEnhance_set_time_pullout
  = unsafePerformIO $
      withCString "AudioEffectStereoEnhance" $
        \ clsNamePtr ->
          withCString "set_time_pullout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectStereoEnhance_set_time_pullout #-}

instance Method "set_time_pullout" GodotAudioEffectStereoEnhance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioEffectStereoEnhance_set_time_pullout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectStereoEnhance_get_time_pullout
  = unsafePerformIO $
      withCString "AudioEffectStereoEnhance" $
        \ clsNamePtr ->
          withCString "get_time_pullout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectStereoEnhance_get_time_pullout #-}

instance Method "get_time_pullout" GodotAudioEffectStereoEnhance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioEffectStereoEnhance_get_time_pullout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectStereoEnhance_set_surround
  = unsafePerformIO $
      withCString "AudioEffectStereoEnhance" $
        \ clsNamePtr ->
          withCString "set_surround" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectStereoEnhance_set_surround #-}

instance Method "set_surround" GodotAudioEffectStereoEnhance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectStereoEnhance_set_surround
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectStereoEnhance_get_surround
  = unsafePerformIO $
      withCString "AudioEffectStereoEnhance" $
        \ clsNamePtr ->
          withCString "get_surround" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectStereoEnhance_get_surround #-}

instance Method "get_surround" GodotAudioEffectStereoEnhance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectStereoEnhance_get_surround
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectPanner = GodotAudioEffectPanner GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectPanner where
        type BaseClass GodotAudioEffectPanner = GodotAudioEffect
        super = coerce
bindAudioEffectPanner_set_pan
  = unsafePerformIO $
      withCString "AudioEffectPanner" $
        \ clsNamePtr ->
          withCString "set_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPanner_set_pan #-}

instance Method "set_pan" GodotAudioEffectPanner (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPanner_set_pan (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPanner_get_pan
  = unsafePerformIO $
      withCString "AudioEffectPanner" $
        \ clsNamePtr ->
          withCString "get_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPanner_get_pan #-}

instance Method "get_pan" GodotAudioEffectPanner (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPanner_get_pan (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectChorus = GodotAudioEffectChorus GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectChorus where
        type BaseClass GodotAudioEffectChorus = GodotAudioEffect
        super = coerce
bindAudioEffectChorus_set_voice_count
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_voice_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_voice_count #-}

instance Method "set_voice_count" GodotAudioEffectChorus
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_voice_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_voice_count
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_voice_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_voice_count #-}

instance Method "get_voice_count" GodotAudioEffectChorus (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_voice_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_voice_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_voice_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_voice_delay_ms #-}

instance Method "set_voice_delay_ms" GodotAudioEffectChorus
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_voice_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_voice_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_voice_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_voice_delay_ms #-}

instance Method "get_voice_delay_ms" GodotAudioEffectChorus
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_voice_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_voice_rate_hz
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_voice_rate_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_voice_rate_hz #-}

instance Method "set_voice_rate_hz" GodotAudioEffectChorus
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_voice_rate_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_voice_rate_hz
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_voice_rate_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_voice_rate_hz #-}

instance Method "get_voice_rate_hz" GodotAudioEffectChorus
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_voice_rate_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_voice_depth_ms
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_voice_depth_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_voice_depth_ms #-}

instance Method "set_voice_depth_ms" GodotAudioEffectChorus
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_voice_depth_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_voice_depth_ms
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_voice_depth_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_voice_depth_ms #-}

instance Method "get_voice_depth_ms" GodotAudioEffectChorus
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_voice_depth_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_voice_level_db
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_voice_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_voice_level_db #-}

instance Method "set_voice_level_db" GodotAudioEffectChorus
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_voice_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_voice_level_db
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_voice_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_voice_level_db #-}

instance Method "get_voice_level_db" GodotAudioEffectChorus
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_voice_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_voice_cutoff_hz
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_voice_cutoff_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_voice_cutoff_hz #-}

instance Method "set_voice_cutoff_hz" GodotAudioEffectChorus
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_voice_cutoff_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_voice_cutoff_hz
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_voice_cutoff_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_voice_cutoff_hz #-}

instance Method "get_voice_cutoff_hz" GodotAudioEffectChorus
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_voice_cutoff_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_voice_pan
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_voice_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_voice_pan #-}

instance Method "set_voice_pan" GodotAudioEffectChorus
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_voice_pan
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_voice_pan
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_voice_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_voice_pan #-}

instance Method "get_voice_pan" GodotAudioEffectChorus
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_voice_pan
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_wet
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_wet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_wet #-}

instance Method "set_wet" GodotAudioEffectChorus (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_wet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_wet
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_wet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_wet #-}

instance Method "get_wet" GodotAudioEffectChorus (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_wet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_set_dry
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "set_dry" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_set_dry #-}

instance Method "set_dry" GodotAudioEffectChorus (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_set_dry (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectChorus_get_dry
  = unsafePerformIO $
      withCString "AudioEffectChorus" $
        \ clsNamePtr ->
          withCString "get_dry" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectChorus_get_dry #-}

instance Method "get_dry" GodotAudioEffectChorus (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectChorus_get_dry (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectDelay = GodotAudioEffectDelay GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectDelay where
        type BaseClass GodotAudioEffectDelay = GodotAudioEffect
        super = coerce
bindAudioEffectDelay_set_dry
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_dry" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_dry #-}

instance Method "set_dry" GodotAudioEffectDelay (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_dry (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_dry
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_dry" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_dry #-}

instance Method "get_dry" GodotAudioEffectDelay (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_dry (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap1_active
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap1_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap1_active #-}

instance Method "set_tap1_active" GodotAudioEffectDelay
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap1_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_is_tap1_active
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "is_tap1_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_is_tap1_active #-}

instance Method "is_tap1_active" GodotAudioEffectDelay (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_is_tap1_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap1_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap1_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap1_delay_ms #-}

instance Method "set_tap1_delay_ms" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap1_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_tap1_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_tap1_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_tap1_delay_ms #-}

instance Method "get_tap1_delay_ms" GodotAudioEffectDelay
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_tap1_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap1_level_db
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap1_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap1_level_db #-}

instance Method "set_tap1_level_db" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap1_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_tap1_level_db
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_tap1_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_tap1_level_db #-}

instance Method "get_tap1_level_db" GodotAudioEffectDelay
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_tap1_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap1_pan
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap1_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap1_pan #-}

instance Method "set_tap1_pan" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap1_pan
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_tap1_pan
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_tap1_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_tap1_pan #-}

instance Method "get_tap1_pan" GodotAudioEffectDelay (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_tap1_pan
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap2_active
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap2_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap2_active #-}

instance Method "set_tap2_active" GodotAudioEffectDelay
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap2_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_is_tap2_active
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "is_tap2_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_is_tap2_active #-}

instance Method "is_tap2_active" GodotAudioEffectDelay (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_is_tap2_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap2_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap2_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap2_delay_ms #-}

instance Method "set_tap2_delay_ms" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap2_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_tap2_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_tap2_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_tap2_delay_ms #-}

instance Method "get_tap2_delay_ms" GodotAudioEffectDelay
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_tap2_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap2_level_db
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap2_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap2_level_db #-}

instance Method "set_tap2_level_db" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap2_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_tap2_level_db
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_tap2_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_tap2_level_db #-}

instance Method "get_tap2_level_db" GodotAudioEffectDelay
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_tap2_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_tap2_pan
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_tap2_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_tap2_pan #-}

instance Method "set_tap2_pan" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_tap2_pan
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_tap2_pan
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_tap2_pan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_tap2_pan #-}

instance Method "get_tap2_pan" GodotAudioEffectDelay (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_tap2_pan
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_feedback_active
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_feedback_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_feedback_active #-}

instance Method "set_feedback_active" GodotAudioEffectDelay
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_feedback_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_is_feedback_active
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "is_feedback_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_is_feedback_active #-}

instance Method "is_feedback_active" GodotAudioEffectDelay
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_is_feedback_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_feedback_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_feedback_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_feedback_delay_ms #-}

instance Method "set_feedback_delay_ms" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_feedback_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_feedback_delay_ms
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_feedback_delay_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_feedback_delay_ms #-}

instance Method "get_feedback_delay_ms" GodotAudioEffectDelay
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_feedback_delay_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_feedback_level_db
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_feedback_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_feedback_level_db #-}

instance Method "set_feedback_level_db" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_feedback_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_feedback_level_db
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_feedback_level_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_feedback_level_db #-}

instance Method "get_feedback_level_db" GodotAudioEffectDelay
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_feedback_level_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_set_feedback_lowpass
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "set_feedback_lowpass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_set_feedback_lowpass #-}

instance Method "set_feedback_lowpass" GodotAudioEffectDelay
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_set_feedback_lowpass
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectDelay_get_feedback_lowpass
  = unsafePerformIO $
      withCString "AudioEffectDelay" $
        \ clsNamePtr ->
          withCString "get_feedback_lowpass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectDelay_get_feedback_lowpass #-}

instance Method "get_feedback_lowpass" GodotAudioEffectDelay
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectDelay_get_feedback_lowpass
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectCompressor = GodotAudioEffectCompressor GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectCompressor where
        type BaseClass GodotAudioEffectCompressor = GodotAudioEffect
        super = coerce
bindAudioEffectCompressor_set_threshold
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "set_threshold" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_set_threshold #-}

instance Method "set_threshold" GodotAudioEffectCompressor
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_set_threshold
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_get_threshold
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "get_threshold" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_get_threshold #-}

instance Method "get_threshold" GodotAudioEffectCompressor
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_get_threshold
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_set_ratio
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "set_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_set_ratio #-}

instance Method "set_ratio" GodotAudioEffectCompressor
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_set_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_get_ratio
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "get_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_get_ratio #-}

instance Method "get_ratio" GodotAudioEffectCompressor (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_get_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_set_gain
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "set_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_set_gain #-}

instance Method "set_gain" GodotAudioEffectCompressor
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_set_gain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_get_gain
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "get_gain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_get_gain #-}

instance Method "get_gain" GodotAudioEffectCompressor (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_get_gain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_set_attack_us
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "set_attack_us" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_set_attack_us #-}

instance Method "set_attack_us" GodotAudioEffectCompressor
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_set_attack_us
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_get_attack_us
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "get_attack_us" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_get_attack_us #-}

instance Method "get_attack_us" GodotAudioEffectCompressor
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_get_attack_us
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_set_release_ms
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "set_release_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_set_release_ms #-}

instance Method "set_release_ms" GodotAudioEffectCompressor
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_set_release_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_get_release_ms
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "get_release_ms" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_get_release_ms #-}

instance Method "get_release_ms" GodotAudioEffectCompressor
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_get_release_ms
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_set_mix
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "set_mix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_set_mix #-}

instance Method "set_mix" GodotAudioEffectCompressor
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_set_mix
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_get_mix
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "get_mix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_get_mix #-}

instance Method "get_mix" GodotAudioEffectCompressor (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_get_mix
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_set_sidechain
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "set_sidechain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_set_sidechain #-}

instance Method "set_sidechain" GodotAudioEffectCompressor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_set_sidechain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectCompressor_get_sidechain
  = unsafePerformIO $
      withCString "AudioEffectCompressor" $
        \ clsNamePtr ->
          withCString "get_sidechain" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectCompressor_get_sidechain #-}

instance Method "get_sidechain" GodotAudioEffectCompressor
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectCompressor_get_sidechain
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectLimiter = GodotAudioEffectLimiter GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectLimiter where
        type BaseClass GodotAudioEffectLimiter = GodotAudioEffect
        super = coerce
bindAudioEffectLimiter_set_ceiling_db
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "set_ceiling_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_set_ceiling_db #-}

instance Method "set_ceiling_db" GodotAudioEffectLimiter
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_set_ceiling_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectLimiter_get_ceiling_db
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "get_ceiling_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_get_ceiling_db #-}

instance Method "get_ceiling_db" GodotAudioEffectLimiter (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_get_ceiling_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectLimiter_set_threshold_db
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "set_threshold_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_set_threshold_db #-}

instance Method "set_threshold_db" GodotAudioEffectLimiter
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_set_threshold_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectLimiter_get_threshold_db
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "get_threshold_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_get_threshold_db #-}

instance Method "get_threshold_db" GodotAudioEffectLimiter
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_get_threshold_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectLimiter_set_soft_clip_db
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "set_soft_clip_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_set_soft_clip_db #-}

instance Method "set_soft_clip_db" GodotAudioEffectLimiter
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_set_soft_clip_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectLimiter_get_soft_clip_db
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "get_soft_clip_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_get_soft_clip_db #-}

instance Method "get_soft_clip_db" GodotAudioEffectLimiter
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_get_soft_clip_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectLimiter_set_soft_clip_ratio
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "set_soft_clip_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_set_soft_clip_ratio #-}

instance Method "set_soft_clip_ratio" GodotAudioEffectLimiter
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_set_soft_clip_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectLimiter_get_soft_clip_ratio
  = unsafePerformIO $
      withCString "AudioEffectLimiter" $
        \ clsNamePtr ->
          withCString "get_soft_clip_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectLimiter_get_soft_clip_ratio #-}

instance Method "get_soft_clip_ratio" GodotAudioEffectLimiter
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectLimiter_get_soft_clip_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectPitchShift = GodotAudioEffectPitchShift GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectPitchShift where
        type BaseClass GodotAudioEffectPitchShift = GodotAudioEffect
        super = coerce
bindAudioEffectPitchShift_set_pitch_scale
  = unsafePerformIO $
      withCString "AudioEffectPitchShift" $
        \ clsNamePtr ->
          withCString "set_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPitchShift_set_pitch_scale #-}

instance Method "set_pitch_scale" GodotAudioEffectPitchShift
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPitchShift_set_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPitchShift_get_pitch_scale
  = unsafePerformIO $
      withCString "AudioEffectPitchShift" $
        \ clsNamePtr ->
          withCString "get_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPitchShift_get_pitch_scale #-}

instance Method "get_pitch_scale" GodotAudioEffectPitchShift
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPitchShift_get_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectPhaser = GodotAudioEffectPhaser GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectPhaser where
        type BaseClass GodotAudioEffectPhaser = GodotAudioEffect
        super = coerce
bindAudioEffectPhaser_set_range_min_hz
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "set_range_min_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_set_range_min_hz #-}

instance Method "set_range_min_hz" GodotAudioEffectPhaser
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_set_range_min_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_get_range_min_hz
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "get_range_min_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_get_range_min_hz #-}

instance Method "get_range_min_hz" GodotAudioEffectPhaser
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_get_range_min_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_set_range_max_hz
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "set_range_max_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_set_range_max_hz #-}

instance Method "set_range_max_hz" GodotAudioEffectPhaser
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_set_range_max_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_get_range_max_hz
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "get_range_max_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_get_range_max_hz #-}

instance Method "get_range_max_hz" GodotAudioEffectPhaser
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_get_range_max_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_set_rate_hz
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "set_rate_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_set_rate_hz #-}

instance Method "set_rate_hz" GodotAudioEffectPhaser
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_set_rate_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_get_rate_hz
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "get_rate_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_get_rate_hz #-}

instance Method "get_rate_hz" GodotAudioEffectPhaser (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_get_rate_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_set_feedback
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "set_feedback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_set_feedback #-}

instance Method "set_feedback" GodotAudioEffectPhaser
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_set_feedback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_get_feedback
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "get_feedback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_get_feedback #-}

instance Method "get_feedback" GodotAudioEffectPhaser (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_get_feedback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_set_depth
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "set_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_set_depth #-}

instance Method "set_depth" GodotAudioEffectPhaser (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_set_depth (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectPhaser_get_depth
  = unsafePerformIO $
      withCString "AudioEffectPhaser" $
        \ clsNamePtr ->
          withCString "get_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectPhaser_get_depth #-}

instance Method "get_depth" GodotAudioEffectPhaser (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectPhaser_get_depth (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioEffectRecord = GodotAudioEffectRecord GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioEffectRecord where
        type BaseClass GodotAudioEffectRecord = GodotAudioEffect
        super = coerce
bindAudioEffectRecord_set_recording_active
  = unsafePerformIO $
      withCString "AudioEffectRecord" $
        \ clsNamePtr ->
          withCString "set_recording_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectRecord_set_recording_active #-}

instance Method "set_recording_active" GodotAudioEffectRecord
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectRecord_set_recording_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectRecord_is_recording_active
  = unsafePerformIO $
      withCString "AudioEffectRecord" $
        \ clsNamePtr ->
          withCString "is_recording_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectRecord_is_recording_active #-}

instance Method "is_recording_active" GodotAudioEffectRecord
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectRecord_is_recording_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectRecord_set_format
  = unsafePerformIO $
      withCString "AudioEffectRecord" $
        \ clsNamePtr ->
          withCString "set_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectRecord_set_format #-}

instance Method "set_format" GodotAudioEffectRecord (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectRecord_set_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectRecord_get_format
  = unsafePerformIO $
      withCString "AudioEffectRecord" $
        \ clsNamePtr ->
          withCString "get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectRecord_get_format #-}

instance Method "get_format" GodotAudioEffectRecord (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectRecord_get_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioEffectRecord_get_recording
  = unsafePerformIO $
      withCString "AudioEffectRecord" $
        \ clsNamePtr ->
          withCString "get_recording" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioEffectRecord_get_recording #-}

instance Method "get_recording" GodotAudioEffectRecord
           (IO GodotAudioStreamSample)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioEffectRecord_get_recording
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysics2DDirectBodyState = GodotPhysics2DDirectBodyState GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DDirectBodyState where
        type BaseClass GodotPhysics2DDirectBodyState = GodotObject
        super = coerce
bindPhysics2DDirectBodyState_get_total_gravity
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_total_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_total_gravity #-}

instance Method "get_total_gravity" GodotPhysics2DDirectBodyState
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_total_gravity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_total_linear_damp
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_total_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_total_linear_damp #-}

instance Method "get_total_linear_damp"
           GodotPhysics2DDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_total_linear_damp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_total_angular_damp
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_total_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_total_angular_damp
             #-}

instance Method "get_total_angular_damp"
           GodotPhysics2DDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_total_angular_damp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_inverse_mass
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_inverse_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_inverse_mass #-}

instance Method "get_inverse_mass" GodotPhysics2DDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_inverse_mass
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_inverse_inertia
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_inverse_inertia" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_inverse_inertia #-}

instance Method "get_inverse_inertia" GodotPhysics2DDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_inverse_inertia
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_set_linear_velocity
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_set_linear_velocity #-}

instance Method "set_linear_velocity" GodotPhysics2DDirectBodyState
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_set_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_linear_velocity
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_linear_velocity #-}

instance Method "get_linear_velocity" GodotPhysics2DDirectBodyState
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_set_angular_velocity
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_set_angular_velocity #-}

instance Method "set_angular_velocity"
           GodotPhysics2DDirectBodyState
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_set_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_angular_velocity
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_angular_velocity #-}

instance Method "get_angular_velocity"
           GodotPhysics2DDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_set_transform
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_set_transform #-}

instance Method "set_transform" GodotPhysics2DDirectBodyState
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_transform
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_transform #-}

instance Method "get_transform" GodotPhysics2DDirectBodyState
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_add_central_force
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "add_central_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_add_central_force #-}

instance Method "add_central_force" GodotPhysics2DDirectBodyState
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_add_central_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_add_force
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "add_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_add_force #-}

instance Method "add_force" GodotPhysics2DDirectBodyState
           (GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_add_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_add_torque
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "add_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_add_torque #-}

instance Method "add_torque" GodotPhysics2DDirectBodyState
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_add_torque
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_apply_central_impulse
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "apply_central_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_apply_central_impulse #-}

instance Method "apply_central_impulse"
           GodotPhysics2DDirectBodyState
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_apply_central_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_apply_torque_impulse
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "apply_torque_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_apply_torque_impulse #-}

instance Method "apply_torque_impulse"
           GodotPhysics2DDirectBodyState
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_apply_torque_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_apply_impulse
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "apply_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_apply_impulse #-}

instance Method "apply_impulse" GodotPhysics2DDirectBodyState
           (GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_apply_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_set_sleep_state
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_sleep_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_set_sleep_state #-}

instance Method "set_sleep_state" GodotPhysics2DDirectBodyState
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_set_sleep_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_is_sleeping
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "is_sleeping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_is_sleeping #-}

instance Method "is_sleeping" GodotPhysics2DDirectBodyState
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_is_sleeping
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_count
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_count #-}

instance Method "get_contact_count" GodotPhysics2DDirectBodyState
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_local_position
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_local_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_local_position
             #-}

instance Method "get_contact_local_position"
           GodotPhysics2DDirectBodyState
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_local_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_local_normal
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_local_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_local_normal
             #-}

instance Method "get_contact_local_normal"
           GodotPhysics2DDirectBodyState
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_local_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_local_shape
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_local_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_local_shape
             #-}

instance Method "get_contact_local_shape"
           GodotPhysics2DDirectBodyState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_local_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_collider
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_collider #-}

instance Method "get_contact_collider"
           GodotPhysics2DDirectBodyState
           (Int -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_collider
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_collider_position
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_collider_position
             #-}

instance Method "get_contact_collider_position"
           GodotPhysics2DDirectBodyState
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_collider_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_collider_id
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_collider_id
             #-}

instance Method "get_contact_collider_id"
           GodotPhysics2DDirectBodyState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_collider_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_collider_object
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_collider_object
             #-}

instance Method "get_contact_collider_object"
           GodotPhysics2DDirectBodyState
           (Int -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_collider_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_collider_shape
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_collider_shape
             #-}

instance Method "get_contact_collider_shape"
           GodotPhysics2DDirectBodyState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_collider_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_collider_shape_metadata
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_shape_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_collider_shape_metadata
             #-}

instance Method "get_contact_collider_shape_metadata"
           GodotPhysics2DDirectBodyState
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_collider_shape_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_contact_collider_velocity_at_position
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_velocity_at_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_contact_collider_velocity_at_position
             #-}

instance Method "get_contact_collider_velocity_at_position"
           GodotPhysics2DDirectBodyState
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_get_contact_collider_velocity_at_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_step
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_step #-}

instance Method "get_step" GodotPhysics2DDirectBodyState (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_get_step
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_integrate_forces
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "integrate_forces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_integrate_forces #-}

instance Method "integrate_forces" GodotPhysics2DDirectBodyState
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectBodyState_integrate_forces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectBodyState_get_space_state
  = unsafePerformIO $
      withCString "Physics2DDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_space_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectBodyState_get_space_state #-}

instance Method "get_space_state" GodotPhysics2DDirectBodyState
           (IO GodotPhysics2DDirectSpaceState)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectBodyState_get_space_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysics2DDirectSpaceState = GodotPhysics2DDirectSpaceState GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DDirectSpaceState where
        type BaseClass GodotPhysics2DDirectSpaceState = GodotObject
        super = coerce
bindPhysics2DDirectSpaceState_intersect_point
  = unsafePerformIO $
      withCString "Physics2DDirectSpaceState" $
        \ clsNamePtr ->
          withCString "intersect_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectSpaceState_intersect_point #-}

instance Method "intersect_point" GodotPhysics2DDirectSpaceState
           (GodotVector2 ->
              Int -> GodotArray -> Int -> Bool -> Bool -> IO GodotArray)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectSpaceState_intersect_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectSpaceState_intersect_ray
  = unsafePerformIO $
      withCString "Physics2DDirectSpaceState" $
        \ clsNamePtr ->
          withCString "intersect_ray" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectSpaceState_intersect_ray #-}

instance Method "intersect_ray" GodotPhysics2DDirectSpaceState
           (GodotVector2 ->
              GodotVector2 ->
                GodotArray -> Int -> Bool -> Bool -> IO GodotDictionary)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectSpaceState_intersect_ray
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectSpaceState_intersect_shape
  = unsafePerformIO $
      withCString "Physics2DDirectSpaceState" $
        \ clsNamePtr ->
          withCString "intersect_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectSpaceState_intersect_shape #-}

instance Method "intersect_shape" GodotPhysics2DDirectSpaceState
           (GodotPhysics2DShapeQueryParameters -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DDirectSpaceState_intersect_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectSpaceState_cast_motion
  = unsafePerformIO $
      withCString "Physics2DDirectSpaceState" $
        \ clsNamePtr ->
          withCString "cast_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectSpaceState_cast_motion #-}

instance Method "cast_motion" GodotPhysics2DDirectSpaceState
           (GodotPhysics2DShapeQueryParameters -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectSpaceState_cast_motion
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectSpaceState_collide_shape
  = unsafePerformIO $
      withCString "Physics2DDirectSpaceState" $
        \ clsNamePtr ->
          withCString "collide_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectSpaceState_collide_shape #-}

instance Method "collide_shape" GodotPhysics2DDirectSpaceState
           (GodotPhysics2DShapeQueryParameters -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectSpaceState_collide_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DDirectSpaceState_get_rest_info
  = unsafePerformIO $
      withCString "Physics2DDirectSpaceState" $
        \ clsNamePtr ->
          withCString "get_rest_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DDirectSpaceState_get_rest_info #-}

instance Method "get_rest_info" GodotPhysics2DDirectSpaceState
           (GodotPhysics2DShapeQueryParameters -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DDirectSpaceState_get_rest_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysics2DShapeQueryResult = GodotPhysics2DShapeQueryResult GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DShapeQueryResult where
        type BaseClass GodotPhysics2DShapeQueryResult = GodotReference
        super = coerce
bindPhysics2DShapeQueryResult_get_result_count
  = unsafePerformIO $
      withCString "Physics2DShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryResult_get_result_count #-}

instance Method "get_result_count" GodotPhysics2DShapeQueryResult
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryResult_get_result_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryResult_get_result_rid
  = unsafePerformIO $
      withCString "Physics2DShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryResult_get_result_rid #-}

instance Method "get_result_rid" GodotPhysics2DShapeQueryResult
           (Int -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DShapeQueryResult_get_result_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryResult_get_result_object_id
  = unsafePerformIO $
      withCString "Physics2DShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_object_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryResult_get_result_object_id #-}

instance Method "get_result_object_id"
           GodotPhysics2DShapeQueryResult
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryResult_get_result_object_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryResult_get_result_object
  = unsafePerformIO $
      withCString "Physics2DShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryResult_get_result_object #-}

instance Method "get_result_object" GodotPhysics2DShapeQueryResult
           (Int -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryResult_get_result_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryResult_get_result_object_shape
  = unsafePerformIO $
      withCString "Physics2DShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_object_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryResult_get_result_object_shape
             #-}

instance Method "get_result_object_shape"
           GodotPhysics2DShapeQueryResult
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryResult_get_result_object_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysics2DTestMotionResult = GodotPhysics2DTestMotionResult GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DTestMotionResult where
        type BaseClass GodotPhysics2DTestMotionResult = GodotReference
        super = coerce
bindPhysics2DTestMotionResult_get_motion
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_motion #-}

instance Method "get_motion" GodotPhysics2DTestMotionResult
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DTestMotionResult_get_motion
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_motion_remainder
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_motion_remainder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_motion_remainder #-}

instance Method "get_motion_remainder"
           GodotPhysics2DTestMotionResult
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DTestMotionResult_get_motion_remainder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_collision_point
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_collision_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_collision_point #-}

instance Method "get_collision_point"
           GodotPhysics2DTestMotionResult
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DTestMotionResult_get_collision_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_collision_normal
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_collision_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_collision_normal #-}

instance Method "get_collision_normal"
           GodotPhysics2DTestMotionResult
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DTestMotionResult_get_collision_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_collider_velocity
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_collider_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_collider_velocity
             #-}

instance Method "get_collider_velocity"
           GodotPhysics2DTestMotionResult
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DTestMotionResult_get_collider_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_collider_id
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_collider_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_collider_id #-}

instance Method "get_collider_id" GodotPhysics2DTestMotionResult
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DTestMotionResult_get_collider_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_collider_rid
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_collider_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_collider_rid #-}

instance Method "get_collider_rid" GodotPhysics2DTestMotionResult
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DTestMotionResult_get_collider_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_collider
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_collider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_collider #-}

instance Method "get_collider" GodotPhysics2DTestMotionResult
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DTestMotionResult_get_collider
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DTestMotionResult_get_collider_shape
  = unsafePerformIO $
      withCString "Physics2DTestMotionResult" $
        \ clsNamePtr ->
          withCString "get_collider_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DTestMotionResult_get_collider_shape #-}

instance Method "get_collider_shape" GodotPhysics2DTestMotionResult
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DTestMotionResult_get_collider_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysics2DShapeQueryParameters = GodotPhysics2DShapeQueryParameters GodotObject
                                               deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DShapeQueryParameters where
        type BaseClass GodotPhysics2DShapeQueryParameters = GodotReference
        super = coerce
bindPhysics2DShapeQueryParameters_set_shape
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_shape #-}

instance Method "set_shape" GodotPhysics2DShapeQueryParameters
           (GodotResource -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DShapeQueryParameters_set_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_shape_rid
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_shape_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_shape_rid #-}

instance Method "set_shape_rid" GodotPhysics2DShapeQueryParameters
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_set_shape_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_get_shape_rid
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_shape_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_get_shape_rid #-}

instance Method "get_shape_rid" GodotPhysics2DShapeQueryParameters
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_get_shape_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_transform
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_transform #-}

instance Method "set_transform" GodotPhysics2DShapeQueryParameters
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_get_transform
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_get_transform #-}

instance Method "get_transform" GodotPhysics2DShapeQueryParameters
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_motion
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_motion #-}

instance Method "set_motion" GodotPhysics2DShapeQueryParameters
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DShapeQueryParameters_set_motion
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_get_motion
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_get_motion #-}

instance Method "get_motion" GodotPhysics2DShapeQueryParameters
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DShapeQueryParameters_get_motion
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_margin
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_margin #-}

instance Method "set_margin" GodotPhysics2DShapeQueryParameters
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DShapeQueryParameters_set_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_get_margin
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_get_margin #-}

instance Method "get_margin" GodotPhysics2DShapeQueryParameters
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysics2DShapeQueryParameters_get_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_collision_layer
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_collision_layer
             #-}

instance Method "set_collision_layer"
           GodotPhysics2DShapeQueryParameters
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_get_collision_layer
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_get_collision_layer
             #-}

instance Method "get_collision_layer"
           GodotPhysics2DShapeQueryParameters
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_get_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_exclude
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_exclude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_exclude #-}

instance Method "set_exclude" GodotPhysics2DShapeQueryParameters
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_set_exclude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_get_exclude
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_exclude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_get_exclude #-}

instance Method "get_exclude" GodotPhysics2DShapeQueryParameters
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_get_exclude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_collide_with_bodies
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_collide_with_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_collide_with_bodies
             #-}

instance Method "set_collide_with_bodies"
           GodotPhysics2DShapeQueryParameters
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_set_collide_with_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_is_collide_with_bodies_enabled
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "is_collide_with_bodies_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_is_collide_with_bodies_enabled
             #-}

instance Method "is_collide_with_bodies_enabled"
           GodotPhysics2DShapeQueryParameters
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_is_collide_with_bodies_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_set_collide_with_areas
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_collide_with_areas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_set_collide_with_areas
             #-}

instance Method "set_collide_with_areas"
           GodotPhysics2DShapeQueryParameters
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_set_collide_with_areas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysics2DShapeQueryParameters_is_collide_with_areas_enabled
  = unsafePerformIO $
      withCString "Physics2DShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "is_collide_with_areas_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysics2DShapeQueryParameters_is_collide_with_areas_enabled
             #-}

instance Method "is_collide_with_areas_enabled"
           GodotPhysics2DShapeQueryParameters
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysics2DShapeQueryParameters_is_collide_with_areas_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsShapeQueryParameters = GodotPhysicsShapeQueryParameters GodotObject
                                             deriving newtype AsVariant

instance HasBaseClass GodotPhysicsShapeQueryParameters where
        type BaseClass GodotPhysicsShapeQueryParameters = GodotReference
        super = coerce
bindPhysicsShapeQueryParameters_set_shape
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_shape #-}

instance Method "set_shape" GodotPhysicsShapeQueryParameters
           (GodotResource -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsShapeQueryParameters_set_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_set_shape_rid
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_shape_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_shape_rid #-}

instance Method "set_shape_rid" GodotPhysicsShapeQueryParameters
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_set_shape_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_get_shape_rid
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_shape_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_get_shape_rid #-}

instance Method "get_shape_rid" GodotPhysicsShapeQueryParameters
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_get_shape_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_set_transform
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_transform #-}

instance Method "set_transform" GodotPhysicsShapeQueryParameters
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_get_transform
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_get_transform #-}

instance Method "get_transform" GodotPhysicsShapeQueryParameters
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_set_margin
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_margin #-}

instance Method "set_margin" GodotPhysicsShapeQueryParameters
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsShapeQueryParameters_set_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_get_margin
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_get_margin #-}

instance Method "get_margin" GodotPhysicsShapeQueryParameters
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsShapeQueryParameters_get_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_set_collision_mask
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_collision_mask #-}

instance Method "set_collision_mask"
           GodotPhysicsShapeQueryParameters
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_get_collision_mask
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_get_collision_mask #-}

instance Method "get_collision_mask"
           GodotPhysicsShapeQueryParameters
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_set_exclude
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_exclude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_exclude #-}

instance Method "set_exclude" GodotPhysicsShapeQueryParameters
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsShapeQueryParameters_set_exclude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_get_exclude
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "get_exclude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_get_exclude #-}

instance Method "get_exclude" GodotPhysicsShapeQueryParameters
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsShapeQueryParameters_get_exclude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_set_collide_with_bodies
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_collide_with_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_collide_with_bodies
             #-}

instance Method "set_collide_with_bodies"
           GodotPhysicsShapeQueryParameters
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_set_collide_with_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_is_collide_with_bodies_enabled
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "is_collide_with_bodies_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_is_collide_with_bodies_enabled
             #-}

instance Method "is_collide_with_bodies_enabled"
           GodotPhysicsShapeQueryParameters
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_is_collide_with_bodies_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_set_collide_with_areas
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "set_collide_with_areas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_set_collide_with_areas
             #-}

instance Method "set_collide_with_areas"
           GodotPhysicsShapeQueryParameters
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_set_collide_with_areas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryParameters_is_collide_with_areas_enabled
  = unsafePerformIO $
      withCString "PhysicsShapeQueryParameters" $
        \ clsNamePtr ->
          withCString "is_collide_with_areas_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryParameters_is_collide_with_areas_enabled
             #-}

instance Method "is_collide_with_areas_enabled"
           GodotPhysicsShapeQueryParameters
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryParameters_is_collide_with_areas_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsDirectBodyState = GodotPhysicsDirectBodyState GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotPhysicsDirectBodyState where
        type BaseClass GodotPhysicsDirectBodyState = GodotObject
        super = coerce
bindPhysicsDirectBodyState_get_total_gravity
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_total_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_total_gravity #-}

instance Method "get_total_gravity" GodotPhysicsDirectBodyState
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_get_total_gravity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_total_linear_damp
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_total_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_total_linear_damp #-}

instance Method "get_total_linear_damp" GodotPhysicsDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_total_linear_damp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_total_angular_damp
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_total_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_total_angular_damp #-}

instance Method "get_total_angular_damp"
           GodotPhysicsDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_total_angular_damp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_center_of_mass
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_center_of_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_center_of_mass #-}

instance Method "get_center_of_mass" GodotPhysicsDirectBodyState
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_center_of_mass
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_principal_inertia_axes
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_principal_inertia_axes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_principal_inertia_axes
             #-}

instance Method "get_principal_inertia_axes"
           GodotPhysicsDirectBodyState
           (IO GodotBasis)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_principal_inertia_axes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_inverse_mass
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_inverse_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_inverse_mass #-}

instance Method "get_inverse_mass" GodotPhysicsDirectBodyState
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_get_inverse_mass
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_inverse_inertia
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_inverse_inertia" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_inverse_inertia #-}

instance Method "get_inverse_inertia" GodotPhysicsDirectBodyState
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_inverse_inertia
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_set_linear_velocity
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_set_linear_velocity #-}

instance Method "set_linear_velocity" GodotPhysicsDirectBodyState
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_set_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_linear_velocity
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_linear_velocity #-}

instance Method "get_linear_velocity" GodotPhysicsDirectBodyState
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_set_angular_velocity
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_set_angular_velocity #-}

instance Method "set_angular_velocity" GodotPhysicsDirectBodyState
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_set_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_angular_velocity
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_angular_velocity #-}

instance Method "get_angular_velocity" GodotPhysicsDirectBodyState
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_set_transform
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_set_transform #-}

instance Method "set_transform" GodotPhysicsDirectBodyState
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_transform
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_transform #-}

instance Method "get_transform" GodotPhysicsDirectBodyState
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_add_central_force
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "add_central_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_add_central_force #-}

instance Method "add_central_force" GodotPhysicsDirectBodyState
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_add_central_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_add_force
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "add_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_add_force #-}

instance Method "add_force" GodotPhysicsDirectBodyState
           (GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_add_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_add_torque
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "add_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_add_torque #-}

instance Method "add_torque" GodotPhysicsDirectBodyState
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_add_torque
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_apply_central_impulse
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "apply_central_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_apply_central_impulse #-}

instance Method "apply_central_impulse" GodotPhysicsDirectBodyState
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_apply_central_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_apply_impulse
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "apply_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_apply_impulse #-}

instance Method "apply_impulse" GodotPhysicsDirectBodyState
           (GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_apply_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_apply_torque_impulse
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "apply_torque_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_apply_torque_impulse #-}

instance Method "apply_torque_impulse" GodotPhysicsDirectBodyState
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_apply_torque_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_set_sleep_state
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "set_sleep_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_set_sleep_state #-}

instance Method "set_sleep_state" GodotPhysicsDirectBodyState
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_set_sleep_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_is_sleeping
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "is_sleeping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_is_sleeping #-}

instance Method "is_sleeping" GodotPhysicsDirectBodyState (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_is_sleeping
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_count
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_count #-}

instance Method "get_contact_count" GodotPhysicsDirectBodyState
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_get_contact_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_local_position
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_local_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_local_position
             #-}

instance Method "get_contact_local_position"
           GodotPhysicsDirectBodyState
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_local_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_local_normal
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_local_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_local_normal
             #-}

instance Method "get_contact_local_normal"
           GodotPhysicsDirectBodyState
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_local_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_impulse
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_impulse #-}

instance Method "get_contact_impulse" GodotPhysicsDirectBodyState
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_local_shape
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_local_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_local_shape #-}

instance Method "get_contact_local_shape"
           GodotPhysicsDirectBodyState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_local_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_collider
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_collider #-}

instance Method "get_contact_collider" GodotPhysicsDirectBodyState
           (Int -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_collider
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_collider_position
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_collider_position
             #-}

instance Method "get_contact_collider_position"
           GodotPhysicsDirectBodyState
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_collider_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_collider_id
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_collider_id #-}

instance Method "get_contact_collider_id"
           GodotPhysicsDirectBodyState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_collider_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_collider_object
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_collider_object
             #-}

instance Method "get_contact_collider_object"
           GodotPhysicsDirectBodyState
           (Int -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_collider_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_collider_shape
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_collider_shape
             #-}

instance Method "get_contact_collider_shape"
           GodotPhysicsDirectBodyState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_collider_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_contact_collider_velocity_at_position
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_contact_collider_velocity_at_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_contact_collider_velocity_at_position
             #-}

instance Method "get_contact_collider_velocity_at_position"
           GodotPhysicsDirectBodyState
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsDirectBodyState_get_contact_collider_velocity_at_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_step
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_step #-}

instance Method "get_step" GodotPhysicsDirectBodyState (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_get_step
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_integrate_forces
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "integrate_forces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_integrate_forces #-}

instance Method "integrate_forces" GodotPhysicsDirectBodyState
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_integrate_forces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectBodyState_get_space_state
  = unsafePerformIO $
      withCString "PhysicsDirectBodyState" $
        \ clsNamePtr ->
          withCString "get_space_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectBodyState_get_space_state #-}

instance Method "get_space_state" GodotPhysicsDirectBodyState
           (IO GodotPhysicsDirectSpaceState)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectBodyState_get_space_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsDirectSpaceState = GodotPhysicsDirectSpaceState GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotPhysicsDirectSpaceState where
        type BaseClass GodotPhysicsDirectSpaceState = GodotObject
        super = coerce
bindPhysicsDirectSpaceState_intersect_ray
  = unsafePerformIO $
      withCString "PhysicsDirectSpaceState" $
        \ clsNamePtr ->
          withCString "intersect_ray" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectSpaceState_intersect_ray #-}

instance Method "intersect_ray" GodotPhysicsDirectSpaceState
           (GodotVector3 ->
              GodotVector3 ->
                GodotArray -> Int -> Bool -> Bool -> IO GodotDictionary)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectSpaceState_intersect_ray
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectSpaceState_intersect_shape
  = unsafePerformIO $
      withCString "PhysicsDirectSpaceState" $
        \ clsNamePtr ->
          withCString "intersect_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectSpaceState_intersect_shape #-}

instance Method "intersect_shape" GodotPhysicsDirectSpaceState
           (GodotPhysicsShapeQueryParameters -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectSpaceState_intersect_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectSpaceState_cast_motion
  = unsafePerformIO $
      withCString "PhysicsDirectSpaceState" $
        \ clsNamePtr ->
          withCString "cast_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectSpaceState_cast_motion #-}

instance Method "cast_motion" GodotPhysicsDirectSpaceState
           (GodotPhysicsShapeQueryParameters -> GodotVector3 -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectSpaceState_cast_motion
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectSpaceState_collide_shape
  = unsafePerformIO $
      withCString "PhysicsDirectSpaceState" $
        \ clsNamePtr ->
          withCString "collide_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectSpaceState_collide_shape #-}

instance Method "collide_shape" GodotPhysicsDirectSpaceState
           (GodotPhysicsShapeQueryParameters -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectSpaceState_collide_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsDirectSpaceState_get_rest_info
  = unsafePerformIO $
      withCString "PhysicsDirectSpaceState" $
        \ clsNamePtr ->
          withCString "get_rest_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsDirectSpaceState_get_rest_info #-}

instance Method "get_rest_info" GodotPhysicsDirectSpaceState
           (GodotPhysicsShapeQueryParameters -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsDirectSpaceState_get_rest_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsShapeQueryResult = GodotPhysicsShapeQueryResult GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotPhysicsShapeQueryResult where
        type BaseClass GodotPhysicsShapeQueryResult = GodotReference
        super = coerce
bindPhysicsShapeQueryResult_get_result_count
  = unsafePerformIO $
      withCString "PhysicsShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryResult_get_result_count #-}

instance Method "get_result_count" GodotPhysicsShapeQueryResult
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsShapeQueryResult_get_result_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryResult_get_result_rid
  = unsafePerformIO $
      withCString "PhysicsShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryResult_get_result_rid #-}

instance Method "get_result_rid" GodotPhysicsShapeQueryResult
           (Int -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsShapeQueryResult_get_result_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryResult_get_result_object_id
  = unsafePerformIO $
      withCString "PhysicsShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_object_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryResult_get_result_object_id #-}

instance Method "get_result_object_id" GodotPhysicsShapeQueryResult
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryResult_get_result_object_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryResult_get_result_object
  = unsafePerformIO $
      withCString "PhysicsShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryResult_get_result_object #-}

instance Method "get_result_object" GodotPhysicsShapeQueryResult
           (Int -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryResult_get_result_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsShapeQueryResult_get_result_object_shape
  = unsafePerformIO $
      withCString "PhysicsShapeQueryResult" $
        \ clsNamePtr ->
          withCString "get_result_object_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsShapeQueryResult_get_result_object_shape
             #-}

instance Method "get_result_object_shape"
           GodotPhysicsShapeQueryResult
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsShapeQueryResult_get_result_object_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNode = GodotNode GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotNode where
        type BaseClass GodotNode = GodotObject
        super = coerce
bindNode__process
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_process" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__process #-}

instance Method "_process" GodotNode (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__process (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__physics_process
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_physics_process" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__physics_process #-}

instance Method "_physics_process" GodotNode (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__physics_process (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__enter_tree
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_enter_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__enter_tree #-}

instance Method "_enter_tree" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__enter_tree (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__exit_tree
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_exit_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__exit_tree #-}

instance Method "_exit_tree" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__exit_tree (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__ready
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_ready" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__ready #-}

instance Method "_ready" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__ready (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__input #-}

instance Method "_input" GodotNode (GodotInputEvent -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__input (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__unhandled_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__unhandled_input #-}

instance Method "_unhandled_input" GodotNode
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__unhandled_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__unhandled_key_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_unhandled_key_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__unhandled_key_input #-}

instance Method "_unhandled_key_input" GodotNode
           (GodotInputEventKey -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__unhandled_key_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__get_configuration_warning
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_get_configuration_warning" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__get_configuration_warning #-}

instance Method "_get_configuration_warning" GodotNode
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__get_configuration_warning
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_add_child_below_node
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "add_child_below_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_add_child_below_node #-}

instance Method "add_child_below_node" GodotNode
           (GodotObject -> GodotObject -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_add_child_below_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_name
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_name #-}

instance Method "set_name" GodotNode (GodotString -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_name (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_name
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_name #-}

instance Method "get_name" GodotNode (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_name (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_add_child
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "add_child" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_add_child #-}

instance Method "add_child" GodotNode
           (GodotObject -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_add_child (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_remove_child
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "remove_child" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_remove_child #-}

instance Method "remove_child" GodotNode (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_remove_child (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_child_count
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_child_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_child_count #-}

instance Method "get_child_count" GodotNode (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_child_count (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_children
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_children" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_children #-}

instance Method "get_children" GodotNode (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_children (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_child
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_child" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_child #-}

instance Method "get_child" GodotNode (Int -> IO GodotNode) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_child (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_has_node
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "has_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_has_node #-}

instance Method "has_node" GodotNode (GodotNodePath -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_has_node (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_node
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_node #-}

instance Method "get_node" GodotNode
           (GodotNodePath -> IO GodotNode)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_node (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_parent
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_parent #-}

instance Method "get_parent" GodotNode (IO GodotNode) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_parent (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_find_node
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "find_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_find_node #-}

instance Method "find_node" GodotNode
           (GodotString -> Bool -> Bool -> IO GodotNode)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_find_node (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_find_parent
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "find_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_find_parent #-}

instance Method "find_parent" GodotNode
           (GodotString -> IO GodotNode)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_find_parent (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_has_node_and_resource
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "has_node_and_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_has_node_and_resource #-}

instance Method "has_node_and_resource" GodotNode
           (GodotNodePath -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_has_node_and_resource (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_node_and_resource
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_node_and_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_node_and_resource #-}

instance Method "get_node_and_resource" GodotNode
           (GodotNodePath -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_node_and_resource (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_inside_tree
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_inside_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_inside_tree #-}

instance Method "is_inside_tree" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_inside_tree (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_a_parent_of
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_a_parent_of" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_a_parent_of #-}

instance Method "is_a_parent_of" GodotNode (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_a_parent_of (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_greater_than
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_greater_than" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_greater_than #-}

instance Method "is_greater_than" GodotNode
           (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_greater_than (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_path
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_path #-}

instance Method "get_path" GodotNode (IO GodotNodePath) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_path (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_path_to
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_path_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_path_to #-}

instance Method "get_path_to" GodotNode
           (GodotObject -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_path_to (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_add_to_group
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "add_to_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_add_to_group #-}

instance Method "add_to_group" GodotNode
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_add_to_group (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_remove_from_group
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "remove_from_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_remove_from_group #-}

instance Method "remove_from_group" GodotNode
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_remove_from_group (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_in_group
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_in_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_in_group #-}

instance Method "is_in_group" GodotNode (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_in_group (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_move_child
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "move_child" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_move_child #-}

instance Method "move_child" GodotNode
           (GodotObject -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_move_child (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_groups
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_groups" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_groups #-}

instance Method "get_groups" GodotNode (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_groups (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_raise
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "raise" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_raise #-}

instance Method "raise" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_raise (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_owner
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_owner #-}

instance Method "set_owner" GodotNode (GodotObject -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_owner (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_owner
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_owner #-}

instance Method "get_owner" GodotNode (IO GodotNode) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_owner (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_remove_and_skip
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "remove_and_skip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_remove_and_skip #-}

instance Method "remove_and_skip" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_remove_and_skip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_index
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_index #-}

instance Method "get_index" GodotNode (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_index (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_print_tree
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "print_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_print_tree #-}

instance Method "print_tree" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_print_tree (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_print_tree_pretty
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "print_tree_pretty" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_print_tree_pretty #-}

instance Method "print_tree_pretty" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_print_tree_pretty (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_filename
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_filename" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_filename #-}

instance Method "set_filename" GodotNode (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_filename (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_filename
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_filename" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_filename #-}

instance Method "get_filename" GodotNode (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_filename (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_propagate_notification
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "propagate_notification" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_propagate_notification #-}

instance Method "propagate_notification" GodotNode (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_propagate_notification (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_propagate_call
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "propagate_call" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_propagate_call #-}

instance Method "propagate_call" GodotNode
           (GodotString -> GodotArray -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_propagate_call (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_physics_process
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_physics_process" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_physics_process #-}

instance Method "set_physics_process" GodotNode (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_physics_process (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_physics_process_delta_time
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_physics_process_delta_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_physics_process_delta_time #-}

instance Method "get_physics_process_delta_time" GodotNode
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_physics_process_delta_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_physics_processing
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_physics_processing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_physics_processing #-}

instance Method "is_physics_processing" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_physics_processing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_process_delta_time
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_process_delta_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_process_delta_time #-}

instance Method "get_process_delta_time" GodotNode (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_process_delta_time (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_process
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_process" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_process #-}

instance Method "set_process" GodotNode (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_process (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_process_priority
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_process_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_process_priority #-}

instance Method "set_process_priority" GodotNode (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_process_priority (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_processing
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_processing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_processing #-}

instance Method "is_processing" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_processing (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_process_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_process_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_process_input #-}

instance Method "set_process_input" GodotNode (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_process_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_processing_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_processing_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_processing_input #-}

instance Method "is_processing_input" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_processing_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_process_unhandled_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_process_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_process_unhandled_input #-}

instance Method "set_process_unhandled_input" GodotNode
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_process_unhandled_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_processing_unhandled_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_processing_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_processing_unhandled_input #-}

instance Method "is_processing_unhandled_input" GodotNode (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_processing_unhandled_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_process_unhandled_key_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_process_unhandled_key_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_process_unhandled_key_input #-}

instance Method "set_process_unhandled_key_input" GodotNode
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_process_unhandled_key_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_processing_unhandled_key_input
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_processing_unhandled_key_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_processing_unhandled_key_input #-}

instance Method "is_processing_unhandled_key_input" GodotNode
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_processing_unhandled_key_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_pause_mode
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_pause_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_pause_mode #-}

instance Method "set_pause_mode" GodotNode (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_pause_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_pause_mode
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_pause_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_pause_mode #-}

instance Method "get_pause_mode" GodotNode (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_pause_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_can_process
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "can_process" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_can_process #-}

instance Method "can_process" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_can_process (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_print_stray_nodes
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "print_stray_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_print_stray_nodes #-}

instance Method "print_stray_nodes" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_print_stray_nodes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_position_in_parent
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_position_in_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_position_in_parent #-}

instance Method "get_position_in_parent" GodotNode (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_position_in_parent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_display_folded
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_display_folded" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_display_folded #-}

instance Method "set_display_folded" GodotNode (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_display_folded (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_displayed_folded
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_displayed_folded" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_displayed_folded #-}

instance Method "is_displayed_folded" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_displayed_folded (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_process_internal
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_process_internal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_process_internal #-}

instance Method "set_process_internal" GodotNode (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_process_internal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_processing_internal
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_processing_internal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_processing_internal #-}

instance Method "is_processing_internal" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_processing_internal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_physics_process_internal
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_physics_process_internal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_physics_process_internal #-}

instance Method "set_physics_process_internal" GodotNode
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_physics_process_internal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_physics_processing_internal
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_physics_processing_internal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_physics_processing_internal #-}

instance Method "is_physics_processing_internal" GodotNode
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_physics_processing_internal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_tree
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_tree #-}

instance Method "get_tree" GodotNode (IO GodotSceneTree) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_tree (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_duplicate
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "duplicate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_duplicate #-}

instance Method "duplicate" GodotNode (Int -> IO GodotNode) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_duplicate (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_replace_by
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "replace_by" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_replace_by #-}

instance Method "replace_by" GodotNode
           (GodotObject -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_replace_by (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_scene_instance_load_placeholder
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_scene_instance_load_placeholder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_scene_instance_load_placeholder #-}

instance Method "set_scene_instance_load_placeholder" GodotNode
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_scene_instance_load_placeholder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_scene_instance_load_placeholder
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_scene_instance_load_placeholder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_scene_instance_load_placeholder #-}

instance Method "get_scene_instance_load_placeholder" GodotNode
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_scene_instance_load_placeholder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_viewport
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_viewport #-}

instance Method "get_viewport" GodotNode (IO GodotViewport) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_viewport (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_queue_free
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "queue_free" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_queue_free #-}

instance Method "queue_free" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_queue_free (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_request_ready
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "request_ready" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_request_ready #-}

instance Method "request_ready" GodotNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_request_ready (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_network_master
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_network_master" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_network_master #-}

instance Method "set_network_master" GodotNode
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_network_master (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_network_master
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_network_master" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_network_master #-}

instance Method "get_network_master" GodotNode (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_network_master (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_is_network_master
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "is_network_master" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_is_network_master #-}

instance Method "is_network_master" GodotNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_is_network_master (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_multiplayer
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_multiplayer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_multiplayer #-}

instance Method "get_multiplayer" GodotNode
           (IO GodotMultiplayerAPI)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_multiplayer (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_get_custom_multiplayer
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "get_custom_multiplayer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_get_custom_multiplayer #-}

instance Method "get_custom_multiplayer" GodotNode
           (IO GodotMultiplayerAPI)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_get_custom_multiplayer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_set_custom_multiplayer
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "set_custom_multiplayer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_set_custom_multiplayer #-}

instance Method "set_custom_multiplayer" GodotNode
           (GodotMultiplayerAPI -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_set_custom_multiplayer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_rpc_config
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "rpc_config" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_rpc_config #-}

instance Method "rpc_config" GodotNode
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_rpc_config (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_rset_config
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "rset_config" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_rset_config #-}

instance Method "rset_config" GodotNode
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_rset_config (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__set_import_path
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_set_import_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__set_import_path #-}

instance Method "_set_import_path" GodotNode
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__set_import_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode__get_import_path
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "_get_import_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode__get_import_path #-}

instance Method "_get_import_path" GodotNode (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode__get_import_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_rset
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "rset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_rset #-}

instance Method "rset" GodotNode
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_rset (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_rset_id
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "rset_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_rset_id #-}

instance Method "rset_id" GodotNode
           (Int -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_rset_id (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_rset_unreliable
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "rset_unreliable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_rset_unreliable #-}

instance Method "rset_unreliable" GodotNode
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_rset_unreliable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode_rset_unreliable_id
  = unsafePerformIO $
      withCString "Node" $
        \ clsNamePtr ->
          withCString "rset_unreliable_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode_rset_unreliable_id #-}

instance Method "rset_unreliable_id" GodotNode
           (Int -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode_rset_unreliable_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInstancePlaceholder = GodotInstancePlaceholder GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotInstancePlaceholder where
        type BaseClass GodotInstancePlaceholder = GodotNode
        super = coerce
bindInstancePlaceholder_get_stored_values
  = unsafePerformIO $
      withCString "InstancePlaceholder" $
        \ clsNamePtr ->
          withCString "get_stored_values" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInstancePlaceholder_get_stored_values #-}

instance Method "get_stored_values" GodotInstancePlaceholder
           (Bool -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInstancePlaceholder_get_stored_values
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInstancePlaceholder_create_instance
  = unsafePerformIO $
      withCString "InstancePlaceholder" $
        \ clsNamePtr ->
          withCString "create_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInstancePlaceholder_create_instance #-}

instance Method "create_instance" GodotInstancePlaceholder
           (Bool -> GodotPackedScene -> IO GodotNode)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInstancePlaceholder_create_instance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInstancePlaceholder_replace_by_instance
  = unsafePerformIO $
      withCString "InstancePlaceholder" $
        \ clsNamePtr ->
          withCString "replace_by_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInstancePlaceholder_replace_by_instance #-}

instance Method "replace_by_instance" GodotInstancePlaceholder
           (GodotPackedScene -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInstancePlaceholder_replace_by_instance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInstancePlaceholder_get_instance_path
  = unsafePerformIO $
      withCString "InstancePlaceholder" $
        \ clsNamePtr ->
          withCString "get_instance_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInstancePlaceholder_get_instance_path #-}

instance Method "get_instance_path" GodotInstancePlaceholder
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInstancePlaceholder_get_instance_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotViewport = GodotViewport GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotViewport where
        type BaseClass GodotViewport = GodotNode
        super = coerce
bindViewport_set_use_arvr
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_use_arvr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_use_arvr #-}

instance Method "set_use_arvr" GodotViewport (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_use_arvr (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_use_arvr
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "use_arvr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_use_arvr #-}

instance Method "use_arvr" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_use_arvr (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_size
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_size #-}

instance Method "set_size" GodotViewport (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_size
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_size #-}

instance Method "get_size" GodotViewport (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_world_2d
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_world_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_world_2d #-}

instance Method "set_world_2d" GodotViewport
           (GodotWorld2D -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_world_2d (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_world_2d
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_world_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_world_2d #-}

instance Method "get_world_2d" GodotViewport (IO GodotWorld2D)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_world_2d (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_find_world_2d
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "find_world_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_find_world_2d #-}

instance Method "find_world_2d" GodotViewport (IO GodotWorld2D)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_find_world_2d (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_world
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_world #-}

instance Method "set_world" GodotViewport (GodotWorld -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_world (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_world
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_world #-}

instance Method "get_world" GodotViewport (IO GodotWorld) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_world (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_find_world
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "find_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_find_world #-}

instance Method "find_world" GodotViewport (IO GodotWorld) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_find_world (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_canvas_transform
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_canvas_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_canvas_transform #-}

instance Method "set_canvas_transform" GodotViewport
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_canvas_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_canvas_transform
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_canvas_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_canvas_transform #-}

instance Method "get_canvas_transform" GodotViewport
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_canvas_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_global_canvas_transform
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_global_canvas_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_global_canvas_transform #-}

instance Method "set_global_canvas_transform" GodotViewport
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_global_canvas_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_global_canvas_transform
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_global_canvas_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_global_canvas_transform #-}

instance Method "get_global_canvas_transform" GodotViewport
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_global_canvas_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_final_transform
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_final_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_final_transform #-}

instance Method "get_final_transform" GodotViewport
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_final_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_visible_rect
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_visible_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_visible_rect #-}

instance Method "get_visible_rect" GodotViewport (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_visible_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_transparent_background
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_transparent_background" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_transparent_background #-}

instance Method "set_transparent_background" GodotViewport
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_transparent_background
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_has_transparent_background
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "has_transparent_background" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_has_transparent_background #-}

instance Method "has_transparent_background" GodotViewport
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_has_transparent_background
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport__vp_input
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "_vp_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport__vp_input #-}

instance Method "_vp_input" GodotViewport
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport__vp_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport__vp_input_text
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "_vp_input_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport__vp_input_text #-}

instance Method "_vp_input_text" GodotViewport
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport__vp_input_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport__vp_unhandled_input
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "_vp_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport__vp_unhandled_input #-}

instance Method "_vp_unhandled_input" GodotViewport
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport__vp_unhandled_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_size_override
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_size_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_size_override #-}

instance Method "set_size_override" GodotViewport
           (Bool -> GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_size_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_size_override
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_size_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_size_override #-}

instance Method "get_size_override" GodotViewport (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_size_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_size_override_enabled
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_size_override_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_size_override_enabled #-}

instance Method "is_size_override_enabled" GodotViewport (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_is_size_override_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_size_override_stretch
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_size_override_stretch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_size_override_stretch #-}

instance Method "set_size_override_stretch" GodotViewport
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_size_override_stretch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_size_override_stretch_enabled
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_size_override_stretch_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_size_override_stretch_enabled #-}

instance Method "is_size_override_stretch_enabled" GodotViewport
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindViewport_is_size_override_stretch_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_vflip
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_vflip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_vflip #-}

instance Method "set_vflip" GodotViewport (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_vflip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_vflip
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_vflip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_vflip #-}

instance Method "get_vflip" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_vflip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_clear_mode
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_clear_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_clear_mode #-}

instance Method "set_clear_mode" GodotViewport (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_clear_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_clear_mode
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_clear_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_clear_mode #-}

instance Method "get_clear_mode" GodotViewport (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_clear_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_update_mode
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_update_mode #-}

instance Method "set_update_mode" GodotViewport (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_update_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_update_mode
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_update_mode #-}

instance Method "get_update_mode" GodotViewport (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_update_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_msaa
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_msaa" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_msaa #-}

instance Method "set_msaa" GodotViewport (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_msaa (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_msaa
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_msaa" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_msaa #-}

instance Method "get_msaa" GodotViewport (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_msaa (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_hdr
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_hdr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_hdr #-}

instance Method "set_hdr" GodotViewport (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_hdr (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_hdr
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_hdr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_hdr #-}

instance Method "get_hdr" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_hdr (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_usage
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_usage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_usage #-}

instance Method "set_usage" GodotViewport (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_usage (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_usage
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_usage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_usage #-}

instance Method "get_usage" GodotViewport (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_usage (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_debug_draw
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_debug_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_debug_draw #-}

instance Method "set_debug_draw" GodotViewport (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_debug_draw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_debug_draw
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_debug_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_debug_draw #-}

instance Method "get_debug_draw" GodotViewport (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_debug_draw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_render_info
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_render_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_render_info #-}

instance Method "get_render_info" GodotViewport (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_render_info (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_texture
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_texture #-}

instance Method "get_texture" GodotViewport
           (IO GodotViewportTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_physics_object_picking
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_physics_object_picking" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_physics_object_picking #-}

instance Method "set_physics_object_picking" GodotViewport
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_physics_object_picking
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_physics_object_picking
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_physics_object_picking" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_physics_object_picking #-}

instance Method "get_physics_object_picking" GodotViewport
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_physics_object_picking
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_viewport_rid
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_viewport_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_viewport_rid #-}

instance Method "get_viewport_rid" GodotViewport (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_viewport_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_input
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_input #-}

instance Method "input" GodotViewport (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_input (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_unhandled_input
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_unhandled_input #-}

instance Method "unhandled_input" GodotViewport
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_unhandled_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_update_worlds
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "update_worlds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_update_worlds #-}

instance Method "update_worlds" GodotViewport (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_update_worlds (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_use_own_world
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_use_own_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_use_own_world #-}

instance Method "set_use_own_world" GodotViewport (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_use_own_world (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_using_own_world
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_using_own_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_using_own_world #-}

instance Method "is_using_own_world" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_is_using_own_world (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_camera
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_camera" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_camera #-}

instance Method "get_camera" GodotViewport (IO GodotCamera) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_camera (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_as_audio_listener
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_as_audio_listener" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_as_audio_listener #-}

instance Method "set_as_audio_listener" GodotViewport
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_as_audio_listener
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_audio_listener
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_audio_listener" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_audio_listener #-}

instance Method "is_audio_listener" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_is_audio_listener (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_as_audio_listener_2d
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_as_audio_listener_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_as_audio_listener_2d #-}

instance Method "set_as_audio_listener_2d" GodotViewport
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_as_audio_listener_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_audio_listener_2d
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_audio_listener_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_audio_listener_2d #-}

instance Method "is_audio_listener_2d" GodotViewport (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_is_audio_listener_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_attach_to_screen_rect
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_attach_to_screen_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_attach_to_screen_rect #-}

instance Method "set_attach_to_screen_rect" GodotViewport
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_attach_to_screen_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_mouse_position
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_mouse_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_mouse_position #-}

instance Method "get_mouse_position" GodotViewport
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_mouse_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_warp_mouse
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "warp_mouse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_warp_mouse #-}

instance Method "warp_mouse" GodotViewport (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_warp_mouse (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_gui_has_modal_stack
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "gui_has_modal_stack" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_gui_has_modal_stack #-}

instance Method "gui_has_modal_stack" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_gui_has_modal_stack
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_gui_get_drag_data
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "gui_get_drag_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_gui_get_drag_data #-}

instance Method "gui_get_drag_data" GodotViewport (IO GodotVariant)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_gui_get_drag_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_gui_is_dragging
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "gui_is_dragging" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_gui_is_dragging #-}

instance Method "gui_is_dragging" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_gui_is_dragging (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_modal_stack_top
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_modal_stack_top" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_modal_stack_top #-}

instance Method "get_modal_stack_top" GodotViewport
           (IO GodotControl)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_modal_stack_top
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_disable_input
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_disable_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_disable_input #-}

instance Method "set_disable_input" GodotViewport (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_disable_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_input_disabled
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_input_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_input_disabled #-}

instance Method "is_input_disabled" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_is_input_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_disable_3d
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_disable_3d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_disable_3d #-}

instance Method "set_disable_3d" GodotViewport (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_disable_3d (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_3d_disabled
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_3d_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_3d_disabled #-}

instance Method "is_3d_disabled" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_is_3d_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_keep_3d_linear
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_keep_3d_linear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_keep_3d_linear #-}

instance Method "set_keep_3d_linear" GodotViewport (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_keep_3d_linear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_keep_3d_linear
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_keep_3d_linear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_keep_3d_linear #-}

instance Method "get_keep_3d_linear" GodotViewport (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_keep_3d_linear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport__gui_show_tooltip
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "_gui_show_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport__gui_show_tooltip #-}

instance Method "_gui_show_tooltip" GodotViewport (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport__gui_show_tooltip (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport__gui_remove_focus
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "_gui_remove_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport__gui_remove_focus #-}

instance Method "_gui_remove_focus" GodotViewport (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport__gui_remove_focus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport__post_gui_grab_click_focus
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "_post_gui_grab_click_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport__post_gui_grab_click_focus #-}

instance Method "_post_gui_grab_click_focus" GodotViewport (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport__post_gui_grab_click_focus
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_shadow_atlas_size
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_shadow_atlas_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_shadow_atlas_size #-}

instance Method "set_shadow_atlas_size" GodotViewport
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_shadow_atlas_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_shadow_atlas_size
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_shadow_atlas_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_shadow_atlas_size #-}

instance Method "get_shadow_atlas_size" GodotViewport (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_get_shadow_atlas_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_snap_controls_to_pixels
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_snap_controls_to_pixels" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_snap_controls_to_pixels #-}

instance Method "set_snap_controls_to_pixels" GodotViewport
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport_set_snap_controls_to_pixels
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_is_snap_controls_to_pixels_enabled
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "is_snap_controls_to_pixels_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_is_snap_controls_to_pixels_enabled #-}

instance Method "is_snap_controls_to_pixels_enabled" GodotViewport
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindViewport_is_snap_controls_to_pixels_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_set_shadow_atlas_quadrant_subdiv
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "set_shadow_atlas_quadrant_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_set_shadow_atlas_quadrant_subdiv #-}

instance Method "set_shadow_atlas_quadrant_subdiv" GodotViewport
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindViewport_set_shadow_atlas_quadrant_subdiv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport_get_shadow_atlas_quadrant_subdiv
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "get_shadow_atlas_quadrant_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport_get_shadow_atlas_quadrant_subdiv #-}

instance Method "get_shadow_atlas_quadrant_subdiv" GodotViewport
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindViewport_get_shadow_atlas_quadrant_subdiv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewport__subwindow_visibility_changed
  = unsafePerformIO $
      withCString "Viewport" $
        \ clsNamePtr ->
          withCString "_subwindow_visibility_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewport__subwindow_visibility_changed #-}

instance Method "_subwindow_visibility_changed" GodotViewport
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewport__subwindow_visibility_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWorld = GodotWorld GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotWorld where
        type BaseClass GodotWorld = GodotResource
        super = coerce
bindWorld_get_space
  = unsafePerformIO $
      withCString "World" $
        \ clsNamePtr ->
          withCString "get_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld_get_space #-}

instance Method "get_space" GodotWorld (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld_get_space (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld_get_scenario
  = unsafePerformIO $
      withCString "World" $
        \ clsNamePtr ->
          withCString "get_scenario" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld_get_scenario #-}

instance Method "get_scenario" GodotWorld (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld_get_scenario (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld_set_environment
  = unsafePerformIO $
      withCString "World" $
        \ clsNamePtr ->
          withCString "set_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld_set_environment #-}

instance Method "set_environment" GodotWorld
           (GodotEnvironment -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld_set_environment (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld_get_environment
  = unsafePerformIO $
      withCString "World" $
        \ clsNamePtr ->
          withCString "get_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld_get_environment #-}

instance Method "get_environment" GodotWorld (IO GodotEnvironment)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld_get_environment (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld_set_fallback_environment
  = unsafePerformIO $
      withCString "World" $
        \ clsNamePtr ->
          withCString "set_fallback_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld_set_fallback_environment #-}

instance Method "set_fallback_environment" GodotWorld
           (GodotEnvironment -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld_set_fallback_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld_get_fallback_environment
  = unsafePerformIO $
      withCString "World" $
        \ clsNamePtr ->
          withCString "get_fallback_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld_get_fallback_environment #-}

instance Method "get_fallback_environment" GodotWorld
           (IO GodotEnvironment)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld_get_fallback_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld_get_direct_space_state
  = unsafePerformIO $
      withCString "World" $
        \ clsNamePtr ->
          withCString "get_direct_space_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld_get_direct_space_state #-}

instance Method "get_direct_space_state" GodotWorld
           (IO GodotPhysicsDirectSpaceState)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld_get_direct_space_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWorld2D = GodotWorld2D GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotWorld2D where
        type BaseClass GodotWorld2D = GodotResource
        super = coerce
bindWorld2D_get_canvas
  = unsafePerformIO $
      withCString "World2D" $
        \ clsNamePtr ->
          withCString "get_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld2D_get_canvas #-}

instance Method "get_canvas" GodotWorld2D (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld2D_get_canvas (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld2D_get_space
  = unsafePerformIO $
      withCString "World2D" $
        \ clsNamePtr ->
          withCString "get_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld2D_get_space #-}

instance Method "get_space" GodotWorld2D (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld2D_get_space (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorld2D_get_direct_space_state
  = unsafePerformIO $
      withCString "World2D" $
        \ clsNamePtr ->
          withCString "get_direct_space_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorld2D_get_direct_space_state #-}

instance Method "get_direct_space_state" GodotWorld2D
           (IO GodotPhysics2DDirectSpaceState)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorld2D_get_direct_space_state
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTexture = GodotTexture GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotTexture where
        type BaseClass GodotTexture = GodotResource
        super = coerce
bindTexture_get_width
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_get_width #-}

instance Method "get_width" GodotTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_get_width (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_get_height
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_get_height #-}

instance Method "get_height" GodotTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_get_height (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_get_size
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_get_size #-}

instance Method "get_size" GodotTexture (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_get_size (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_has_alpha
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "has_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_has_alpha #-}

instance Method "has_alpha" GodotTexture (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_has_alpha (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_set_flags
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "set_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_set_flags #-}

instance Method "set_flags" GodotTexture (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_set_flags (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_get_flags
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "get_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_get_flags #-}

instance Method "get_flags" GodotTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_get_flags (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_draw
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_draw #-}

instance Method "draw" GodotTexture
           (GodotRid ->
              GodotVector2 -> GodotColor -> Bool -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_draw (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_draw_rect
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "draw_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_draw_rect #-}

instance Method "draw_rect" GodotTexture
           (GodotRid ->
              GodotRect2 -> Bool -> GodotColor -> Bool -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_draw_rect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_draw_rect_region
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "draw_rect_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_draw_rect_region #-}

instance Method "draw_rect_region" GodotTexture
           (GodotRid ->
              GodotRect2 ->
                GodotRect2 -> GodotColor -> Bool -> GodotTexture -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_draw_rect_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTexture_get_data
  = unsafePerformIO $
      withCString "Texture" $
        \ clsNamePtr ->
          withCString "get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTexture_get_data #-}

instance Method "get_data" GodotTexture (IO GodotImage) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTexture_get_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotViewportTexture = GodotViewportTexture GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotViewportTexture where
        type BaseClass GodotViewportTexture = GodotTexture
        super = coerce
bindViewportTexture_set_viewport_path_in_scene
  = unsafePerformIO $
      withCString "ViewportTexture" $
        \ clsNamePtr ->
          withCString "set_viewport_path_in_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewportTexture_set_viewport_path_in_scene #-}

instance Method "set_viewport_path_in_scene" GodotViewportTexture
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindViewportTexture_set_viewport_path_in_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewportTexture_get_viewport_path_in_scene
  = unsafePerformIO $
      withCString "ViewportTexture" $
        \ clsNamePtr ->
          withCString "get_viewport_path_in_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewportTexture_get_viewport_path_in_scene #-}

instance Method "get_viewport_path_in_scene" GodotViewportTexture
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindViewportTexture_get_viewport_path_in_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotHTTPRequest = GodotHTTPRequest GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotHTTPRequest where
        type BaseClass GodotHTTPRequest = GodotNode
        super = coerce
bindHTTPRequest_request
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "request" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_request #-}

instance Method "request" GodotHTTPRequest
           (GodotString ->
              GodotPoolStringArray -> Bool -> Int -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_request (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_cancel_request
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "cancel_request" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_cancel_request #-}

instance Method "cancel_request" GodotHTTPRequest (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_cancel_request (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_get_http_client_status
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "get_http_client_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_get_http_client_status #-}

instance Method "get_http_client_status" GodotHTTPRequest (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_get_http_client_status
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_set_use_threads
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "set_use_threads" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_set_use_threads #-}

instance Method "set_use_threads" GodotHTTPRequest (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_set_use_threads (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_is_using_threads
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "is_using_threads" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_is_using_threads #-}

instance Method "is_using_threads" GodotHTTPRequest (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_is_using_threads
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_set_body_size_limit
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "set_body_size_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_set_body_size_limit #-}

instance Method "set_body_size_limit" GodotHTTPRequest
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_set_body_size_limit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_get_body_size_limit
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "get_body_size_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_get_body_size_limit #-}

instance Method "get_body_size_limit" GodotHTTPRequest (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_get_body_size_limit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_set_max_redirects
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "set_max_redirects" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_set_max_redirects #-}

instance Method "set_max_redirects" GodotHTTPRequest (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_set_max_redirects
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_get_max_redirects
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "get_max_redirects" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_get_max_redirects #-}

instance Method "get_max_redirects" GodotHTTPRequest (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_get_max_redirects
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_set_download_file
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "set_download_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_set_download_file #-}

instance Method "set_download_file" GodotHTTPRequest
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_set_download_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_get_download_file
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "get_download_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_get_download_file #-}

instance Method "get_download_file" GodotHTTPRequest
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_get_download_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_get_downloaded_bytes
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "get_downloaded_bytes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_get_downloaded_bytes #-}

instance Method "get_downloaded_bytes" GodotHTTPRequest (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_get_downloaded_bytes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest_get_body_size
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "get_body_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest_get_body_size #-}

instance Method "get_body_size" GodotHTTPRequest (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest_get_body_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest__redirect_request
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "_redirect_request" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest__redirect_request #-}

instance Method "_redirect_request" GodotHTTPRequest
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest__redirect_request
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHTTPRequest__request_done
  = unsafePerformIO $
      withCString "HTTPRequest" $
        \ clsNamePtr ->
          withCString "_request_done" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHTTPRequest__request_done #-}

instance Method "_request_done" GodotHTTPRequest
           (Int -> Int -> GodotPoolStringArray -> GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHTTPRequest__request_done (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTimer = GodotTimer GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotTimer where
        type BaseClass GodotTimer = GodotNode
        super = coerce
bindTimer_set_wait_time
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "set_wait_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_set_wait_time #-}

instance Method "set_wait_time" GodotTimer (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_set_wait_time (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_get_wait_time
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "get_wait_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_get_wait_time #-}

instance Method "get_wait_time" GodotTimer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_get_wait_time (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_set_one_shot
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "set_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_set_one_shot #-}

instance Method "set_one_shot" GodotTimer (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_set_one_shot (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_is_one_shot
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "is_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_is_one_shot #-}

instance Method "is_one_shot" GodotTimer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_is_one_shot (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_set_autostart
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "set_autostart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_set_autostart #-}

instance Method "set_autostart" GodotTimer (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_set_autostart (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_has_autostart
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "has_autostart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_has_autostart #-}

instance Method "has_autostart" GodotTimer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_has_autostart (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_start
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_start #-}

instance Method "start" GodotTimer (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_start (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_stop
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_stop #-}

instance Method "stop" GodotTimer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_stop (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_set_paused
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "set_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_set_paused #-}

instance Method "set_paused" GodotTimer (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_set_paused (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_is_paused
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "is_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_is_paused #-}

instance Method "is_paused" GodotTimer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_is_paused (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_is_stopped
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "is_stopped" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_is_stopped #-}

instance Method "is_stopped" GodotTimer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_is_stopped (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_get_time_left
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "get_time_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_get_time_left #-}

instance Method "get_time_left" GodotTimer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_get_time_left (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_set_timer_process_mode
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "set_timer_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_set_timer_process_mode #-}

instance Method "set_timer_process_mode" GodotTimer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_set_timer_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTimer_get_timer_process_mode
  = unsafePerformIO $
      withCString "Timer" $
        \ clsNamePtr ->
          withCString "get_timer_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTimer_get_timer_process_mode #-}

instance Method "get_timer_process_mode" GodotTimer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTimer_get_timer_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCanvasLayer = GodotCanvasLayer GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotCanvasLayer where
        type BaseClass GodotCanvasLayer = GodotNode
        super = coerce
bindCanvasLayer_set_layer
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "set_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_set_layer #-}

instance Method "set_layer" GodotCanvasLayer (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_set_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_layer
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_layer #-}

instance Method "get_layer" GodotCanvasLayer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_set_transform
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_set_transform #-}

instance Method "set_transform" GodotCanvasLayer
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_set_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_transform
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_transform #-}

instance Method "get_transform" GodotCanvasLayer
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_set_offset
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_set_offset #-}

instance Method "set_offset" GodotCanvasLayer
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_set_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_offset
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_offset #-}

instance Method "get_offset" GodotCanvasLayer (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_set_rotation
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "set_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_set_rotation #-}

instance Method "set_rotation" GodotCanvasLayer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_set_rotation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_rotation
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_rotation #-}

instance Method "get_rotation" GodotCanvasLayer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_rotation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_set_rotation_degrees
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "set_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_set_rotation_degrees #-}

instance Method "set_rotation_degrees" GodotCanvasLayer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_set_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_rotation_degrees
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_rotation_degrees #-}

instance Method "get_rotation_degrees" GodotCanvasLayer (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_set_scale
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "set_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_set_scale #-}

instance Method "set_scale" GodotCanvasLayer
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_set_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_scale
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_scale #-}

instance Method "get_scale" GodotCanvasLayer (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_set_custom_viewport
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "set_custom_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_set_custom_viewport #-}

instance Method "set_custom_viewport" GodotCanvasLayer
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_set_custom_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_custom_viewport
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_custom_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_custom_viewport #-}

instance Method "get_custom_viewport" GodotCanvasLayer
           (IO GodotNode)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_custom_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasLayer_get_canvas
  = unsafePerformIO $
      withCString "CanvasLayer" $
        \ clsNamePtr ->
          withCString "get_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasLayer_get_canvas #-}

instance Method "get_canvas" GodotCanvasLayer (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasLayer_get_canvas (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCanvasItem = GodotCanvasItem GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotCanvasItem where
        type BaseClass GodotCanvasItem = GodotNode
        super = coerce
bindCanvasItem__draw
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__draw #-}

instance Method "_draw" GodotCanvasItem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__draw (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__toplevel_raise_self
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_toplevel_raise_self" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__toplevel_raise_self #-}

instance Method "_toplevel_raise_self" GodotCanvasItem (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__toplevel_raise_self
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__update_callback
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_update_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__update_callback #-}

instance Method "_update_callback" GodotCanvasItem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__update_callback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_set_state
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_set_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_set_state #-}

instance Method "_edit_set_state" GodotCanvasItem
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_set_state (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_get_state
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_get_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_get_state #-}

instance Method "_edit_get_state" GodotCanvasItem
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_get_state (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_set_position
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_set_position #-}

instance Method "_edit_set_position" GodotCanvasItem
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_set_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_get_position
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_get_position #-}

instance Method "_edit_get_position" GodotCanvasItem
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_set_scale
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_set_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_set_scale #-}

instance Method "_edit_set_scale" GodotCanvasItem
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_set_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_get_scale
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_get_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_get_scale #-}

instance Method "_edit_get_scale" GodotCanvasItem (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_get_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_set_rect
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_set_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_set_rect #-}

instance Method "_edit_set_rect" GodotCanvasItem
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_set_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_get_rect
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_get_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_get_rect #-}

instance Method "_edit_get_rect" GodotCanvasItem (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_get_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_use_rect
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_use_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_use_rect #-}

instance Method "_edit_use_rect" GodotCanvasItem (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_use_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_set_rotation
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_set_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_set_rotation #-}

instance Method "_edit_set_rotation" GodotCanvasItem
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_set_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_get_rotation
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_get_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_get_rotation #-}

instance Method "_edit_get_rotation" GodotCanvasItem (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_get_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_use_rotation
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_use_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_use_rotation #-}

instance Method "_edit_use_rotation" GodotCanvasItem (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_use_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_set_pivot
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_set_pivot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_set_pivot #-}

instance Method "_edit_set_pivot" GodotCanvasItem
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_set_pivot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_get_pivot
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_get_pivot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_get_pivot #-}

instance Method "_edit_get_pivot" GodotCanvasItem (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_get_pivot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__edit_use_pivot
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_edit_use_pivot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__edit_use_pivot #-}

instance Method "_edit_use_pivot" GodotCanvasItem (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__edit_use_pivot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_canvas_item
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_canvas_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_canvas_item #-}

instance Method "get_canvas_item" GodotCanvasItem (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_canvas_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_visible
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_visible #-}

instance Method "set_visible" GodotCanvasItem (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_is_visible
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "is_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_is_visible #-}

instance Method "is_visible" GodotCanvasItem (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_is_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_is_visible_in_tree
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "is_visible_in_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_is_visible_in_tree #-}

instance Method "is_visible_in_tree" GodotCanvasItem (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_is_visible_in_tree
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_show
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "show" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_show #-}

instance Method "show" GodotCanvasItem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_show (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_hide
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "hide" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_hide #-}

instance Method "hide" GodotCanvasItem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_hide (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_update
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_update #-}

instance Method "update" GodotCanvasItem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_update (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_as_toplevel
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_as_toplevel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_as_toplevel #-}

instance Method "set_as_toplevel" GodotCanvasItem (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_as_toplevel (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_is_set_as_toplevel
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "is_set_as_toplevel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_is_set_as_toplevel #-}

instance Method "is_set_as_toplevel" GodotCanvasItem (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_is_set_as_toplevel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_light_mask
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_light_mask #-}

instance Method "set_light_mask" GodotCanvasItem (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_light_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_light_mask
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_light_mask #-}

instance Method "get_light_mask" GodotCanvasItem (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_light_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_modulate
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_modulate #-}

instance Method "set_modulate" GodotCanvasItem
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_modulate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_modulate
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_modulate #-}

instance Method "get_modulate" GodotCanvasItem (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_modulate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_self_modulate
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_self_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_self_modulate #-}

instance Method "set_self_modulate" GodotCanvasItem
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_self_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_self_modulate
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_self_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_self_modulate #-}

instance Method "get_self_modulate" GodotCanvasItem (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_self_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_draw_behind_parent
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_draw_behind_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_draw_behind_parent #-}

instance Method "set_draw_behind_parent" GodotCanvasItem
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_draw_behind_parent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_is_draw_behind_parent_enabled
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "is_draw_behind_parent_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_is_draw_behind_parent_enabled #-}

instance Method "is_draw_behind_parent_enabled" GodotCanvasItem
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_is_draw_behind_parent_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__set_on_top
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_set_on_top" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__set_on_top #-}

instance Method "_set_on_top" GodotCanvasItem (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__set_on_top (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem__is_on_top
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "_is_on_top" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem__is_on_top #-}

instance Method "_is_on_top" GodotCanvasItem (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem__is_on_top (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_line
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_line #-}

instance Method "draw_line" GodotCanvasItem
           (GodotVector2 ->
              GodotVector2 -> GodotColor -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_line (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_polyline
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_polyline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_polyline #-}

instance Method "draw_polyline" GodotCanvasItem
           (GodotPoolVector2Array -> GodotColor -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_polyline (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_polyline_colors
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_polyline_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_polyline_colors #-}

instance Method "draw_polyline_colors" GodotCanvasItem
           (GodotPoolVector2Array ->
              GodotPoolColorArray -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_polyline_colors
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_multiline
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_multiline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_multiline #-}

instance Method "draw_multiline" GodotCanvasItem
           (GodotPoolVector2Array -> GodotColor -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_multiline (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_multiline_colors
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_multiline_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_multiline_colors #-}

instance Method "draw_multiline_colors" GodotCanvasItem
           (GodotPoolVector2Array ->
              GodotPoolColorArray -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_multiline_colors
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_rect
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_rect #-}

instance Method "draw_rect" GodotCanvasItem
           (GodotRect2 -> GodotColor -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_rect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_circle
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_circle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_circle #-}

instance Method "draw_circle" GodotCanvasItem
           (GodotVector2 -> Float -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_circle (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_texture
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_texture #-}

instance Method "draw_texture" GodotCanvasItem
           (GodotTexture ->
              GodotVector2 -> GodotColor -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_texture_rect
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_texture_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_texture_rect #-}

instance Method "draw_texture_rect" GodotCanvasItem
           (GodotTexture ->
              GodotRect2 -> Bool -> GodotColor -> Bool -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_texture_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_texture_rect_region
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_texture_rect_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_texture_rect_region #-}

instance Method "draw_texture_rect_region" GodotCanvasItem
           (GodotTexture ->
              GodotRect2 ->
                GodotRect2 -> GodotColor -> Bool -> GodotTexture -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_texture_rect_region
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_style_box
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_style_box" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_style_box #-}

instance Method "draw_style_box" GodotCanvasItem
           (GodotStyleBox -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_style_box (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_primitive
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_primitive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_primitive #-}

instance Method "draw_primitive" GodotCanvasItem
           (GodotPoolVector2Array ->
              GodotPoolColorArray ->
                GodotPoolVector2Array ->
                  GodotTexture -> Float -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_primitive (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_polygon
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_polygon #-}

instance Method "draw_polygon" GodotCanvasItem
           (GodotPoolVector2Array ->
              GodotPoolColorArray ->
                GodotPoolVector2Array ->
                  GodotTexture -> GodotTexture -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_colored_polygon
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_colored_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_colored_polygon #-}

instance Method "draw_colored_polygon" GodotCanvasItem
           (GodotPoolVector2Array ->
              GodotColor ->
                GodotPoolVector2Array ->
                  GodotTexture -> GodotTexture -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_colored_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_string
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_string #-}

instance Method "draw_string" GodotCanvasItem
           (GodotFont ->
              GodotVector2 -> GodotString -> GodotColor -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_char
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_char" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_char #-}

instance Method "draw_char" GodotCanvasItem
           (GodotFont ->
              GodotVector2 ->
                GodotString -> GodotString -> GodotColor -> IO Float)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_char (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_mesh
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_mesh #-}

instance Method "draw_mesh" GodotCanvasItem
           (GodotMesh -> GodotTexture -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_mesh (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_multimesh
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_multimesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_multimesh #-}

instance Method "draw_multimesh" GodotCanvasItem
           (GodotMesh -> GodotTexture -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_multimesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_set_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_set_transform #-}

instance Method "draw_set_transform" GodotCanvasItem
           (GodotVector2 -> Float -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_draw_set_transform_matrix
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "draw_set_transform_matrix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_draw_set_transform_matrix #-}

instance Method "draw_set_transform_matrix" GodotCanvasItem
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_draw_set_transform_matrix
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_transform #-}

instance Method "get_transform" GodotCanvasItem
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_global_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_global_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_global_transform #-}

instance Method "get_global_transform" GodotCanvasItem
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_global_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_global_transform_with_canvas
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_global_transform_with_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_global_transform_with_canvas #-}

instance Method "get_global_transform_with_canvas" GodotCanvasItem
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCanvasItem_get_global_transform_with_canvas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_viewport_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_viewport_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_viewport_transform #-}

instance Method "get_viewport_transform" GodotCanvasItem
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_viewport_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_viewport_rect
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_viewport_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_viewport_rect #-}

instance Method "get_viewport_rect" GodotCanvasItem (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_viewport_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_canvas_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_canvas_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_canvas_transform #-}

instance Method "get_canvas_transform" GodotCanvasItem
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_canvas_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_local_mouse_position
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_local_mouse_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_local_mouse_position #-}

instance Method "get_local_mouse_position" GodotCanvasItem
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_local_mouse_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_global_mouse_position
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_global_mouse_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_global_mouse_position #-}

instance Method "get_global_mouse_position" GodotCanvasItem
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_global_mouse_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_canvas
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_canvas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_canvas #-}

instance Method "get_canvas" GodotCanvasItem (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_canvas (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_world_2d
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_world_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_world_2d #-}

instance Method "get_world_2d" GodotCanvasItem (IO GodotWorld2D)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_world_2d (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_material
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_material #-}

instance Method "set_material" GodotCanvasItem
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_material
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_material #-}

instance Method "get_material" GodotCanvasItem (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_use_parent_material
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_use_parent_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_use_parent_material #-}

instance Method "set_use_parent_material" GodotCanvasItem
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_use_parent_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_get_use_parent_material
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "get_use_parent_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_get_use_parent_material #-}

instance Method "get_use_parent_material" GodotCanvasItem (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_get_use_parent_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_notify_local_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_notify_local_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_notify_local_transform #-}

instance Method "set_notify_local_transform" GodotCanvasItem
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_notify_local_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_is_local_transform_notification_enabled
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "is_local_transform_notification_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_is_local_transform_notification_enabled
             #-}

instance Method "is_local_transform_notification_enabled"
           GodotCanvasItem
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCanvasItem_is_local_transform_notification_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_set_notify_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "set_notify_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_set_notify_transform #-}

instance Method "set_notify_transform" GodotCanvasItem
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_set_notify_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_is_transform_notification_enabled
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "is_transform_notification_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_is_transform_notification_enabled #-}

instance Method "is_transform_notification_enabled" GodotCanvasItem
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCanvasItem_is_transform_notification_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_force_update_transform
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "force_update_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_force_update_transform #-}

instance Method "force_update_transform" GodotCanvasItem (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_force_update_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_make_canvas_position_local
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "make_canvas_position_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_make_canvas_position_local #-}

instance Method "make_canvas_position_local" GodotCanvasItem
           (GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_make_canvas_position_local
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItem_make_input_local
  = unsafePerformIO $
      withCString "CanvasItem" $
        \ clsNamePtr ->
          withCString "make_input_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItem_make_input_local #-}

instance Method "make_input_local" GodotCanvasItem
           (GodotInputEvent -> IO GodotInputEvent)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItem_make_input_local (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNode2D = GodotNode2D GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotNode2D where
        type BaseClass GodotNode2D = GodotCanvasItem
        super = coerce
bindNode2D_get_transform
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_transform #-}

instance Method "get_transform" GodotNode2D (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_transform (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_global_transform
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_global_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_global_transform #-}

instance Method "get_global_transform" GodotNode2D
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_global_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_position
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_position #-}

instance Method "set_position" GodotNode2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_position (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_rotation
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_rotation #-}

instance Method "set_rotation" GodotNode2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_rotation (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_rotation_degrees
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_rotation_degrees #-}

instance Method "set_rotation_degrees" GodotNode2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_rotation_degrees (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_scale
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_scale #-}

instance Method "set_scale" GodotNode2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_scale (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_position
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_position #-}

instance Method "get_position" GodotNode2D (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_position (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_rotation
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_rotation #-}

instance Method "get_rotation" GodotNode2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_rotation (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_rotation_degrees
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_rotation_degrees #-}

instance Method "get_rotation_degrees" GodotNode2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_rotation_degrees (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_scale
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_scale #-}

instance Method "get_scale" GodotNode2D (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_scale (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_rotate
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "rotate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_rotate #-}

instance Method "rotate" GodotNode2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_rotate (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_move_local_x
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "move_local_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_move_local_x #-}

instance Method "move_local_x" GodotNode2D (Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_move_local_x (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_move_local_y
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "move_local_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_move_local_y #-}

instance Method "move_local_y" GodotNode2D (Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_move_local_y (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_translate
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "translate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_translate #-}

instance Method "translate" GodotNode2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_translate (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_global_translate
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "global_translate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_global_translate #-}

instance Method "global_translate" GodotNode2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_global_translate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_apply_scale
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "apply_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_apply_scale #-}

instance Method "apply_scale" GodotNode2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_apply_scale (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_global_position
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_global_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_global_position #-}

instance Method "set_global_position" GodotNode2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_global_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_global_position
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_global_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_global_position #-}

instance Method "get_global_position" GodotNode2D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_global_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_global_rotation
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_global_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_global_rotation #-}

instance Method "set_global_rotation" GodotNode2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_global_rotation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_global_rotation
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_global_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_global_rotation #-}

instance Method "get_global_rotation" GodotNode2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_global_rotation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_global_rotation_degrees
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_global_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_global_rotation_degrees #-}

instance Method "set_global_rotation_degrees" GodotNode2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_global_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_global_rotation_degrees
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_global_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_global_rotation_degrees #-}

instance Method "get_global_rotation_degrees" GodotNode2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_global_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_global_scale
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_global_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_global_scale #-}

instance Method "set_global_scale" GodotNode2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_global_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_global_scale
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_global_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_global_scale #-}

instance Method "get_global_scale" GodotNode2D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_global_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_transform
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_transform #-}

instance Method "set_transform" GodotNode2D
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_transform (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_global_transform
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_global_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_global_transform #-}

instance Method "set_global_transform" GodotNode2D
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_global_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_look_at
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "look_at" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_look_at #-}

instance Method "look_at" GodotNode2D (GodotVector2 -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_look_at (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_angle_to
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_angle_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_angle_to #-}

instance Method "get_angle_to" GodotNode2D
           (GodotVector2 -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_angle_to (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_to_local
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "to_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_to_local #-}

instance Method "to_local" GodotNode2D
           (GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_to_local (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_to_global
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "to_global" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_to_global #-}

instance Method "to_global" GodotNode2D
           (GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_to_global (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_z_index
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_z_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_z_index #-}

instance Method "set_z_index" GodotNode2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_z_index (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_z_index
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_z_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_z_index #-}

instance Method "get_z_index" GodotNode2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_z_index (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_set_z_as_relative
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "set_z_as_relative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_set_z_as_relative #-}

instance Method "set_z_as_relative" GodotNode2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_set_z_as_relative (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_is_z_relative
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "is_z_relative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_is_z_relative #-}

instance Method "is_z_relative" GodotNode2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_is_z_relative (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNode2D_get_relative_transform_to_parent
  = unsafePerformIO $
      withCString "Node2D" $
        \ clsNamePtr ->
          withCString "get_relative_transform_to_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNode2D_get_relative_transform_to_parent #-}

instance Method "get_relative_transform_to_parent" GodotNode2D
           (GodotObject -> IO GodotTransform2d)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNode2D_get_relative_transform_to_parent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCanvasModulate = GodotCanvasModulate GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotCanvasModulate where
        type BaseClass GodotCanvasModulate = GodotNode2D
        super = coerce
bindCanvasModulate_set_color
  = unsafePerformIO $
      withCString "CanvasModulate" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasModulate_set_color #-}

instance Method "set_color" GodotCanvasModulate
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasModulate_set_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasModulate_get_color
  = unsafePerformIO $
      withCString "CanvasModulate" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasModulate_get_color #-}

instance Method "get_color" GodotCanvasModulate (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasModulate_get_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotResourcePreloader = GodotResourcePreloader GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotResourcePreloader where
        type BaseClass GodotResourcePreloader = GodotNode
        super = coerce
bindResourcePreloader__set_resources
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "_set_resources" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader__set_resources #-}

instance Method "_set_resources" GodotResourcePreloader
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader__set_resources
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourcePreloader__get_resources
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "_get_resources" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader__get_resources #-}

instance Method "_get_resources" GodotResourcePreloader
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader__get_resources
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourcePreloader_add_resource
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "add_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader_add_resource #-}

instance Method "add_resource" GodotResourcePreloader
           (GodotString -> GodotResource -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader_add_resource
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourcePreloader_remove_resource
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "remove_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader_remove_resource #-}

instance Method "remove_resource" GodotResourcePreloader
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader_remove_resource
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourcePreloader_rename_resource
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "rename_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader_rename_resource #-}

instance Method "rename_resource" GodotResourcePreloader
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader_rename_resource
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourcePreloader_has_resource
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "has_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader_has_resource #-}

instance Method "has_resource" GodotResourcePreloader
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader_has_resource
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourcePreloader_get_resource
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "get_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader_get_resource #-}

instance Method "get_resource" GodotResourcePreloader
           (GodotString -> IO GodotResource)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader_get_resource
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindResourcePreloader_get_resource_list
  = unsafePerformIO $
      withCString "ResourcePreloader" $
        \ clsNamePtr ->
          withCString "get_resource_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindResourcePreloader_get_resource_list #-}

instance Method "get_resource_list" GodotResourcePreloader
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindResourcePreloader_get_resource_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotButtonGroup = GodotButtonGroup GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotButtonGroup where
        type BaseClass GodotButtonGroup = GodotResource
        super = coerce
bindButtonGroup_get_pressed_button
  = unsafePerformIO $
      withCString "ButtonGroup" $
        \ clsNamePtr ->
          withCString "get_pressed_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButtonGroup_get_pressed_button #-}

instance Method "get_pressed_button" GodotButtonGroup
           (IO GodotBaseButton)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButtonGroup_get_pressed_button
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotControl = GodotControl GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotControl where
        type BaseClass GodotControl = GodotCanvasItem
        super = coerce
bindControl__gui_input
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__gui_input #-}

instance Method "_gui_input" GodotControl
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__get_minimum_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_get_minimum_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__get_minimum_size #-}

instance Method "_get_minimum_size" GodotControl (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__get_minimum_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_drag_data
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_drag_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_drag_data #-}

instance Method "get_drag_data" GodotControl
           (GodotVector2 -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_drag_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_can_drop_data
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "can_drop_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_can_drop_data #-}

instance Method "can_drop_data" GodotControl
           (GodotVector2 -> GodotVariant -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_can_drop_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_drop_data
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "drop_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_drop_data #-}

instance Method "drop_data" GodotControl
           (GodotVector2 -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_drop_data (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__make_custom_tooltip
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_make_custom_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__make_custom_tooltip #-}

instance Method "_make_custom_tooltip" GodotControl
           (GodotString -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__make_custom_tooltip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__clips_input
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_clips_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__clips_input #-}

instance Method "_clips_input" GodotControl (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__clips_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_point
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_point #-}

instance Method "has_point" GodotControl (GodotVector2 -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__size_changed
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_size_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__size_changed #-}

instance Method "_size_changed" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__size_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__update_minimum_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_update_minimum_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__update_minimum_size #-}

instance Method "_update_minimum_size" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__update_minimum_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_accept_event
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "accept_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_accept_event #-}

instance Method "accept_event" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_accept_event (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_minimum_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_minimum_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_minimum_size #-}

instance Method "get_minimum_size" GodotControl (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_minimum_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_combined_minimum_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_combined_minimum_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_combined_minimum_size #-}

instance Method "get_combined_minimum_size" GodotControl
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_combined_minimum_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_anchors_preset
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_anchors_preset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_anchors_preset #-}

instance Method "set_anchors_preset" GodotControl
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_anchors_preset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_margins_preset
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_margins_preset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_margins_preset #-}

instance Method "set_margins_preset" GodotControl
           (Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_margins_preset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_anchors_and_margins_preset
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_anchors_and_margins_preset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_anchors_and_margins_preset #-}

instance Method "set_anchors_and_margins_preset" GodotControl
           (Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_anchors_and_margins_preset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_anchor
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_anchor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_anchor #-}

instance Method "set_anchor" GodotControl
           (Int -> Float -> Bool -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_anchor (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__set_anchor
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_set_anchor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__set_anchor #-}

instance Method "_set_anchor" GodotControl (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__set_anchor (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_anchor
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_anchor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_anchor #-}

instance Method "get_anchor" GodotControl (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_anchor (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_margin
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_margin #-}

instance Method "set_margin" GodotControl (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_margin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_anchor_and_margin
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_anchor_and_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_anchor_and_margin #-}

instance Method "set_anchor_and_margin" GodotControl
           (Int -> Float -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_anchor_and_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_begin
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_begin #-}

instance Method "set_begin" GodotControl (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_begin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_end
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_end #-}

instance Method "set_end" GodotControl (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_end (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_position
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_position #-}

instance Method "set_position" GodotControl (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_position (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_size #-}

instance Method "set_size" GodotControl (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_size (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_custom_minimum_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_custom_minimum_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_custom_minimum_size #-}

instance Method "set_custom_minimum_size" GodotControl
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_custom_minimum_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_global_position
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_global_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_global_position #-}

instance Method "set_global_position" GodotControl
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_global_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_rotation
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_rotation #-}

instance Method "set_rotation" GodotControl (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_rotation (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_rotation_degrees
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_rotation_degrees #-}

instance Method "set_rotation_degrees" GodotControl
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_scale
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_scale #-}

instance Method "set_scale" GodotControl (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_scale (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_pivot_offset
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_pivot_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_pivot_offset #-}

instance Method "set_pivot_offset" GodotControl
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_pivot_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_margin
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_margin #-}

instance Method "get_margin" GodotControl (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_margin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_begin
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_begin #-}

instance Method "get_begin" GodotControl (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_begin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_end
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_end #-}

instance Method "get_end" GodotControl (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_end (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_position
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_position #-}

instance Method "get_position" GodotControl (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_position (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_size #-}

instance Method "get_size" GodotControl (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_size (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_rotation
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_rotation #-}

instance Method "get_rotation" GodotControl (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_rotation (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_rotation_degrees
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_rotation_degrees #-}

instance Method "get_rotation_degrees" GodotControl (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_scale
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_scale #-}

instance Method "get_scale" GodotControl (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_scale (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_pivot_offset
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_pivot_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_pivot_offset #-}

instance Method "get_pivot_offset" GodotControl (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_pivot_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_custom_minimum_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_custom_minimum_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_custom_minimum_size #-}

instance Method "get_custom_minimum_size" GodotControl
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_custom_minimum_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_parent_area_size
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_parent_area_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_parent_area_size #-}

instance Method "get_parent_area_size" GodotControl
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_parent_area_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_global_position
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_global_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_global_position #-}

instance Method "get_global_position" GodotControl
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_global_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_rect
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_rect #-}

instance Method "get_rect" GodotControl (IO GodotRect2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_rect (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_global_rect
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_global_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_global_rect #-}

instance Method "get_global_rect" GodotControl (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_global_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_show_modal
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "show_modal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_show_modal #-}

instance Method "show_modal" GodotControl (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_show_modal (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_focus_mode
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_focus_mode #-}

instance Method "set_focus_mode" GodotControl (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_focus_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_focus_mode
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_focus_mode #-}

instance Method "get_focus_mode" GodotControl (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_focus_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_focus
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_focus #-}

instance Method "has_focus" GodotControl (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_focus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_grab_focus
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "grab_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_grab_focus #-}

instance Method "grab_focus" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_grab_focus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_release_focus
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "release_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_release_focus #-}

instance Method "release_focus" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_release_focus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_focus_owner
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_focus_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_focus_owner #-}

instance Method "get_focus_owner" GodotControl (IO GodotControl)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_focus_owner (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_h_size_flags
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_h_size_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_h_size_flags #-}

instance Method "set_h_size_flags" GodotControl (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_h_size_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_h_size_flags
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_h_size_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_h_size_flags #-}

instance Method "get_h_size_flags" GodotControl (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_h_size_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_stretch_ratio
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_stretch_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_stretch_ratio #-}

instance Method "set_stretch_ratio" GodotControl (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_stretch_ratio (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_stretch_ratio
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_stretch_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_stretch_ratio #-}

instance Method "get_stretch_ratio" GodotControl (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_stretch_ratio (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_v_size_flags
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_v_size_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_v_size_flags #-}

instance Method "set_v_size_flags" GodotControl (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_v_size_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_v_size_flags
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_v_size_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_v_size_flags #-}

instance Method "get_v_size_flags" GodotControl (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_v_size_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_theme
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_theme" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_theme #-}

instance Method "set_theme" GodotControl (GodotTheme -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_theme (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_theme
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_theme" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_theme #-}

instance Method "get_theme" GodotControl (IO GodotTheme) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_theme (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_add_icon_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "add_icon_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_add_icon_override #-}

instance Method "add_icon_override" GodotControl
           (GodotString -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_add_icon_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_add_shader_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "add_shader_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_add_shader_override #-}

instance Method "add_shader_override" GodotControl
           (GodotString -> GodotShader -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_add_shader_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_add_stylebox_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "add_stylebox_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_add_stylebox_override #-}

instance Method "add_stylebox_override" GodotControl
           (GodotString -> GodotStyleBox -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_add_stylebox_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_add_font_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "add_font_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_add_font_override #-}

instance Method "add_font_override" GodotControl
           (GodotString -> GodotFont -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_add_font_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_add_color_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "add_color_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_add_color_override #-}

instance Method "add_color_override" GodotControl
           (GodotString -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_add_color_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_add_constant_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "add_constant_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_add_constant_override #-}

instance Method "add_constant_override" GodotControl
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_add_constant_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_icon
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_icon #-}

instance Method "get_icon" GodotControl
           (GodotString -> GodotString -> IO GodotTexture)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_icon (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_stylebox
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_stylebox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_stylebox #-}

instance Method "get_stylebox" GodotControl
           (GodotString -> GodotString -> IO GodotStyleBox)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_stylebox (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_font
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_font #-}

instance Method "get_font" GodotControl
           (GodotString -> GodotString -> IO GodotFont)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_font (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_color
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_color #-}

instance Method "get_color" GodotControl
           (GodotString -> GodotString -> IO GodotColor)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_constant
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_constant #-}

instance Method "get_constant" GodotControl
           (GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_constant (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_icon_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_icon_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_icon_override #-}

instance Method "has_icon_override" GodotControl
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_icon_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_shader_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_shader_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_shader_override #-}

instance Method "has_shader_override" GodotControl
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_shader_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_stylebox_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_stylebox_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_stylebox_override #-}

instance Method "has_stylebox_override" GodotControl
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_stylebox_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_font_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_font_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_font_override #-}

instance Method "has_font_override" GodotControl
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_font_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_color_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_color_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_color_override #-}

instance Method "has_color_override" GodotControl
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_color_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_constant_override
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_constant_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_constant_override #-}

instance Method "has_constant_override" GodotControl
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_constant_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_icon
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_icon #-}

instance Method "has_icon" GodotControl
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_icon (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_stylebox
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_stylebox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_stylebox #-}

instance Method "has_stylebox" GodotControl
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_stylebox (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_font
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_font #-}

instance Method "has_font" GodotControl
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_font (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_color
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_color #-}

instance Method "has_color" GodotControl
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_has_constant
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "has_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_has_constant #-}

instance Method "has_constant" GodotControl
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_has_constant (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_parent_control
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_parent_control" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_parent_control #-}

instance Method "get_parent_control" GodotControl (IO GodotControl)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_parent_control (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_h_grow_direction
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_h_grow_direction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_h_grow_direction #-}

instance Method "set_h_grow_direction" GodotControl (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_h_grow_direction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_h_grow_direction
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_h_grow_direction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_h_grow_direction #-}

instance Method "get_h_grow_direction" GodotControl (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_h_grow_direction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_v_grow_direction
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_v_grow_direction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_v_grow_direction #-}

instance Method "set_v_grow_direction" GodotControl (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_v_grow_direction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_v_grow_direction
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_v_grow_direction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_v_grow_direction #-}

instance Method "get_v_grow_direction" GodotControl (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_v_grow_direction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_tooltip
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_tooltip #-}

instance Method "set_tooltip" GodotControl (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_tooltip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_tooltip
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_tooltip #-}

instance Method "get_tooltip" GodotControl
           (GodotVector2 -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_tooltip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__get_tooltip
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_get_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__get_tooltip #-}

instance Method "_get_tooltip" GodotControl (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__get_tooltip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_default_cursor_shape
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_default_cursor_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_default_cursor_shape #-}

instance Method "set_default_cursor_shape" GodotControl
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_default_cursor_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_default_cursor_shape
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_default_cursor_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_default_cursor_shape #-}

instance Method "get_default_cursor_shape" GodotControl (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_default_cursor_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_cursor_shape
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_cursor_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_cursor_shape #-}

instance Method "get_cursor_shape" GodotControl
           (GodotVector2 -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_cursor_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_focus_neighbour
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_focus_neighbour" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_focus_neighbour #-}

instance Method "set_focus_neighbour" GodotControl
           (Int -> GodotNodePath -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_focus_neighbour (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_focus_neighbour
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_focus_neighbour" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_focus_neighbour #-}

instance Method "get_focus_neighbour" GodotControl
           (Int -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_focus_neighbour (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_focus_next
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_focus_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_focus_next #-}

instance Method "set_focus_next" GodotControl
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_focus_next (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_focus_next
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_focus_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_focus_next #-}

instance Method "get_focus_next" GodotControl (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_focus_next (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_focus_previous
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_focus_previous" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_focus_previous #-}

instance Method "set_focus_previous" GodotControl
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_focus_previous (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_focus_previous
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_focus_previous" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_focus_previous #-}

instance Method "get_focus_previous" GodotControl
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_focus_previous (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_force_drag
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "force_drag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_force_drag #-}

instance Method "force_drag" GodotControl
           (GodotVariant -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_force_drag (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_mouse_filter
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_mouse_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_mouse_filter #-}

instance Method "set_mouse_filter" GodotControl (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_mouse_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_get_mouse_filter
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "get_mouse_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_get_mouse_filter #-}

instance Method "get_mouse_filter" GodotControl (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_get_mouse_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_clip_contents
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_clip_contents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_clip_contents #-}

instance Method "set_clip_contents" GodotControl (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_clip_contents (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_is_clipping_contents
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "is_clipping_contents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_is_clipping_contents #-}

instance Method "is_clipping_contents" GodotControl (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_is_clipping_contents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_grab_click_focus
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "grab_click_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_grab_click_focus #-}

instance Method "grab_click_focus" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_grab_click_focus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_drag_forwarding
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_drag_forwarding" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_drag_forwarding #-}

instance Method "set_drag_forwarding" GodotControl
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_drag_forwarding (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_set_drag_preview
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "set_drag_preview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_set_drag_preview #-}

instance Method "set_drag_preview" GodotControl
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_set_drag_preview (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_warp_mouse
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "warp_mouse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_warp_mouse #-}

instance Method "warp_mouse" GodotControl (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_warp_mouse (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl_minimum_size_changed
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "minimum_size_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl_minimum_size_changed #-}

instance Method "minimum_size_changed" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl_minimum_size_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__theme_changed
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_theme_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__theme_changed #-}

instance Method "_theme_changed" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__theme_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindControl__font_changed
  = unsafePerformIO $
      withCString "Control" $
        \ clsNamePtr ->
          withCString "_font_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindControl__font_changed #-}

instance Method "_font_changed" GodotControl (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindControl__font_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTheme = GodotTheme GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotTheme where
        type BaseClass GodotTheme = GodotResource
        super = coerce
bindTheme_set_icon
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "set_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_set_icon #-}

instance Method "set_icon" GodotTheme
           (GodotString -> GodotString -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_set_icon (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_icon
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_icon #-}

instance Method "get_icon" GodotTheme
           (GodotString -> GodotString -> IO GodotTexture)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_icon (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_has_icon
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "has_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_has_icon #-}

instance Method "has_icon" GodotTheme
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_has_icon (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_clear_icon
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "clear_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_clear_icon #-}

instance Method "clear_icon" GodotTheme
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_clear_icon (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_icon_list
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_icon_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_icon_list #-}

instance Method "get_icon_list" GodotTheme
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_icon_list (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_set_stylebox
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "set_stylebox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_set_stylebox #-}

instance Method "set_stylebox" GodotTheme
           (GodotString -> GodotString -> GodotStyleBox -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_set_stylebox (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_stylebox
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_stylebox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_stylebox #-}

instance Method "get_stylebox" GodotTheme
           (GodotString -> GodotString -> IO GodotStyleBox)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_stylebox (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_has_stylebox
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "has_stylebox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_has_stylebox #-}

instance Method "has_stylebox" GodotTheme
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_has_stylebox (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_clear_stylebox
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "clear_stylebox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_clear_stylebox #-}

instance Method "clear_stylebox" GodotTheme
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_clear_stylebox (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_stylebox_list
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_stylebox_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_stylebox_list #-}

instance Method "get_stylebox_list" GodotTheme
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_stylebox_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_stylebox_types
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_stylebox_types" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_stylebox_types #-}

instance Method "get_stylebox_types" GodotTheme
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_stylebox_types (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_set_font
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "set_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_set_font #-}

instance Method "set_font" GodotTheme
           (GodotString -> GodotString -> GodotFont -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_set_font (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_font
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_font #-}

instance Method "get_font" GodotTheme
           (GodotString -> GodotString -> IO GodotFont)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_font (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_has_font
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "has_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_has_font #-}

instance Method "has_font" GodotTheme
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_has_font (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_clear_font
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "clear_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_clear_font #-}

instance Method "clear_font" GodotTheme
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_clear_font (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_font_list
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_font_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_font_list #-}

instance Method "get_font_list" GodotTheme
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_font_list (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_set_color
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_set_color #-}

instance Method "set_color" GodotTheme
           (GodotString -> GodotString -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_set_color (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_color
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_color #-}

instance Method "get_color" GodotTheme
           (GodotString -> GodotString -> IO GodotColor)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_color (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_has_color
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "has_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_has_color #-}

instance Method "has_color" GodotTheme
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_has_color (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_clear_color
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "clear_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_clear_color #-}

instance Method "clear_color" GodotTheme
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_clear_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_color_list
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_color_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_color_list #-}

instance Method "get_color_list" GodotTheme
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_color_list (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_set_constant
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "set_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_set_constant #-}

instance Method "set_constant" GodotTheme
           (GodotString -> GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_set_constant (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_constant
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_constant #-}

instance Method "get_constant" GodotTheme
           (GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_constant (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_has_constant
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "has_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_has_constant #-}

instance Method "has_constant" GodotTheme
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_has_constant (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_clear_constant
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "clear_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_clear_constant #-}

instance Method "clear_constant" GodotTheme
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_clear_constant (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_constant_list
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_constant_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_constant_list #-}

instance Method "get_constant_list" GodotTheme
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_constant_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_set_default_font
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "set_default_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_set_default_font #-}

instance Method "set_default_font" GodotTheme (GodotFont -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_set_default_font (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_default_font
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_default_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_default_font #-}

instance Method "get_default_font" GodotTheme (IO GodotFont) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_default_font (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_get_type_list
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "get_type_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_get_type_list #-}

instance Method "get_type_list" GodotTheme
           (GodotString -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_get_type_list (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme__emit_theme_changed
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "_emit_theme_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme__emit_theme_changed #-}

instance Method "_emit_theme_changed" GodotTheme (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme__emit_theme_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTheme_copy_default_theme
  = unsafePerformIO $
      withCString "Theme" $
        \ clsNamePtr ->
          withCString "copy_default_theme" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTheme_copy_default_theme #-}

instance Method "copy_default_theme" GodotTheme (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTheme_copy_default_theme (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBaseButton = GodotBaseButton GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotBaseButton where
        type BaseClass GodotBaseButton = GodotControl
        super = coerce
bindBaseButton__pressed
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton__pressed #-}

instance Method "_pressed" GodotBaseButton (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton__pressed (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton__toggled
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "_toggled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton__toggled #-}

instance Method "_toggled" GodotBaseButton (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton__toggled (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton__gui_input
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton__gui_input #-}

instance Method "_gui_input" GodotBaseButton
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton__gui_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton__unhandled_input
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton__unhandled_input #-}

instance Method "_unhandled_input" GodotBaseButton
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton__unhandled_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_pressed
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_pressed #-}

instance Method "set_pressed" GodotBaseButton (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_is_pressed
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_is_pressed #-}

instance Method "is_pressed" GodotBaseButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_is_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_is_hovered
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "is_hovered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_is_hovered #-}

instance Method "is_hovered" GodotBaseButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_is_hovered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_toggle_mode
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_toggle_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_toggle_mode #-}

instance Method "set_toggle_mode" GodotBaseButton (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_toggle_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_is_toggle_mode
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "is_toggle_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_is_toggle_mode #-}

instance Method "is_toggle_mode" GodotBaseButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_is_toggle_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_disabled
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_disabled #-}

instance Method "set_disabled" GodotBaseButton (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_is_disabled
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "is_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_is_disabled #-}

instance Method "is_disabled" GodotBaseButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_is_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_action_mode
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_action_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_action_mode #-}

instance Method "set_action_mode" GodotBaseButton (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_action_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_get_action_mode
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "get_action_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_get_action_mode #-}

instance Method "get_action_mode" GodotBaseButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_get_action_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_button_mask
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_button_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_button_mask #-}

instance Method "set_button_mask" GodotBaseButton (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_button_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_get_button_mask
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "get_button_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_get_button_mask #-}

instance Method "get_button_mask" GodotBaseButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_get_button_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_get_draw_mode
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "get_draw_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_get_draw_mode #-}

instance Method "get_draw_mode" GodotBaseButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_get_draw_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_enabled_focus_mode
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_enabled_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_enabled_focus_mode #-}

instance Method "set_enabled_focus_mode" GodotBaseButton
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_enabled_focus_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_get_enabled_focus_mode
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "get_enabled_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_get_enabled_focus_mode #-}

instance Method "get_enabled_focus_mode" GodotBaseButton (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_get_enabled_focus_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_shortcut
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_shortcut #-}

instance Method "set_shortcut" GodotBaseButton
           (GodotShortCut -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_get_shortcut
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "get_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_get_shortcut #-}

instance Method "get_shortcut" GodotBaseButton (IO GodotShortCut)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_get_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_set_button_group
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "set_button_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_set_button_group #-}

instance Method "set_button_group" GodotBaseButton
           (GodotButtonGroup -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_set_button_group (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBaseButton_get_button_group
  = unsafePerformIO $
      withCString "BaseButton" $
        \ clsNamePtr ->
          withCString "get_button_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBaseButton_get_button_group #-}

instance Method "get_button_group" GodotBaseButton
           (IO GodotButtonGroup)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBaseButton_get_button_group (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotShortCut = GodotShortCut GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotShortCut where
        type BaseClass GodotShortCut = GodotResource
        super = coerce
bindShortCut_set_shortcut
  = unsafePerformIO $
      withCString "ShortCut" $
        \ clsNamePtr ->
          withCString "set_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShortCut_set_shortcut #-}

instance Method "set_shortcut" GodotShortCut
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShortCut_set_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShortCut_get_shortcut
  = unsafePerformIO $
      withCString "ShortCut" $
        \ clsNamePtr ->
          withCString "get_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShortCut_get_shortcut #-}

instance Method "get_shortcut" GodotShortCut (IO GodotInputEvent)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShortCut_get_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShortCut_is_valid
  = unsafePerformIO $
      withCString "ShortCut" $
        \ clsNamePtr ->
          withCString "is_valid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShortCut_is_valid #-}

instance Method "is_valid" GodotShortCut (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShortCut_is_valid (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShortCut_is_shortcut
  = unsafePerformIO $
      withCString "ShortCut" $
        \ clsNamePtr ->
          withCString "is_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShortCut_is_shortcut #-}

instance Method "is_shortcut" GodotShortCut
           (GodotInputEvent -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShortCut_is_shortcut (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShortCut_get_as_text
  = unsafePerformIO $
      withCString "ShortCut" $
        \ clsNamePtr ->
          withCString "get_as_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShortCut_get_as_text #-}

instance Method "get_as_text" GodotShortCut (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShortCut_get_as_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotButton = GodotButton GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotButton where
        type BaseClass GodotButton = GodotBaseButton
        super = coerce
bindButton_set_text
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_set_text #-}

instance Method "set_text" GodotButton (GodotString -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_set_text (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_get_text
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_get_text #-}

instance Method "get_text" GodotButton (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_get_text (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_set_button_icon
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "set_button_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_set_button_icon #-}

instance Method "set_button_icon" GodotButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_set_button_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_get_button_icon
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "get_button_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_get_button_icon #-}

instance Method "get_button_icon" GodotButton (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_get_button_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_set_flat
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "set_flat" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_set_flat #-}

instance Method "set_flat" GodotButton (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_set_flat (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_set_clip_text
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "set_clip_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_set_clip_text #-}

instance Method "set_clip_text" GodotButton (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_set_clip_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_get_clip_text
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "get_clip_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_get_clip_text #-}

instance Method "get_clip_text" GodotButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_get_clip_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_set_text_align
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "set_text_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_set_text_align #-}

instance Method "set_text_align" GodotButton (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_set_text_align (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_get_text_align
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "get_text_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_get_text_align #-}

instance Method "get_text_align" GodotButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_get_text_align (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindButton_is_flat
  = unsafePerformIO $
      withCString "Button" $
        \ clsNamePtr ->
          withCString "is_flat" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindButton_is_flat #-}

instance Method "is_flat" GodotButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindButton_is_flat (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotLabel = GodotLabel GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotLabel where
        type BaseClass GodotLabel = GodotControl
        super = coerce
bindLabel_set_align
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_align #-}

instance Method "set_align" GodotLabel (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_align (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_align
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_align #-}

instance Method "get_align" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_align (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_valign
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_valign" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_valign #-}

instance Method "set_valign" GodotLabel (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_valign (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_valign
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_valign" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_valign #-}

instance Method "get_valign" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_valign (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_text
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_text #-}

instance Method "set_text" GodotLabel (GodotString -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_text (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_text
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_text #-}

instance Method "get_text" GodotLabel (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_text (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_autowrap
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_autowrap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_autowrap #-}

instance Method "set_autowrap" GodotLabel (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_autowrap (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_has_autowrap
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "has_autowrap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_has_autowrap #-}

instance Method "has_autowrap" GodotLabel (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_has_autowrap (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_clip_text
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_clip_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_clip_text #-}

instance Method "set_clip_text" GodotLabel (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_clip_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_is_clipping_text
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "is_clipping_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_is_clipping_text #-}

instance Method "is_clipping_text" GodotLabel (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_is_clipping_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_uppercase
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_uppercase" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_uppercase #-}

instance Method "set_uppercase" GodotLabel (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_uppercase (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_is_uppercase
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "is_uppercase" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_is_uppercase #-}

instance Method "is_uppercase" GodotLabel (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_is_uppercase (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_line_height
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_line_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_line_height #-}

instance Method "get_line_height" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_line_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_line_count
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_line_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_line_count #-}

instance Method "get_line_count" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_line_count (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_visible_line_count
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_visible_line_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_visible_line_count #-}

instance Method "get_visible_line_count" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_visible_line_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_total_character_count
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_total_character_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_total_character_count #-}

instance Method "get_total_character_count" GodotLabel (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_total_character_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_visible_characters
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_visible_characters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_visible_characters #-}

instance Method "set_visible_characters" GodotLabel (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_visible_characters
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_visible_characters
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_visible_characters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_visible_characters #-}

instance Method "get_visible_characters" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_visible_characters
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_percent_visible
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_percent_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_percent_visible #-}

instance Method "set_percent_visible" GodotLabel (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_percent_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_percent_visible
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_percent_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_percent_visible #-}

instance Method "get_percent_visible" GodotLabel (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_percent_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_lines_skipped
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_lines_skipped" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_lines_skipped #-}

instance Method "set_lines_skipped" GodotLabel (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_lines_skipped (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_lines_skipped
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_lines_skipped" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_lines_skipped #-}

instance Method "get_lines_skipped" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_lines_skipped (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_set_max_lines_visible
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "set_max_lines_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_set_max_lines_visible #-}

instance Method "set_max_lines_visible" GodotLabel (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_set_max_lines_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLabel_get_max_lines_visible
  = unsafePerformIO $
      withCString "Label" $
        \ clsNamePtr ->
          withCString "get_max_lines_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLabel_get_max_lines_visible #-}

instance Method "get_max_lines_visible" GodotLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLabel_get_max_lines_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRange = GodotRange GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotRange where
        type BaseClass GodotRange = GodotControl
        super = coerce
bindRange_get_value
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "get_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_get_value #-}

instance Method "get_value" GodotRange (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_get_value (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_get_min
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "get_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_get_min #-}

instance Method "get_min" GodotRange (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_get_min (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_get_max
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "get_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_get_max #-}

instance Method "get_max" GodotRange (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_get_max (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_get_step
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "get_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_get_step #-}

instance Method "get_step" GodotRange (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_get_step (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_get_page
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "get_page" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_get_page #-}

instance Method "get_page" GodotRange (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_get_page (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_get_as_ratio
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "get_as_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_get_as_ratio #-}

instance Method "get_as_ratio" GodotRange (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_get_as_ratio (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_value
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_value #-}

instance Method "set_value" GodotRange (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_value (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_min
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_min #-}

instance Method "set_min" GodotRange (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_min (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_max
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_max #-}

instance Method "set_max" GodotRange (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_max (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_step
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_step #-}

instance Method "set_step" GodotRange (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_step (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_page
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_page" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_page #-}

instance Method "set_page" GodotRange (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_page (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_as_ratio
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_as_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_as_ratio #-}

instance Method "set_as_ratio" GodotRange (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_as_ratio (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_use_rounded_values
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_use_rounded_values" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_use_rounded_values #-}

instance Method "set_use_rounded_values" GodotRange (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_use_rounded_values
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_is_using_rounded_values
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "is_using_rounded_values" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_is_using_rounded_values #-}

instance Method "is_using_rounded_values" GodotRange (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_is_using_rounded_values
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_exp_ratio
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_exp_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_exp_ratio #-}

instance Method "set_exp_ratio" GodotRange (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_exp_ratio (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_is_ratio_exp
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "is_ratio_exp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_is_ratio_exp #-}

instance Method "is_ratio_exp" GodotRange (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_is_ratio_exp (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_allow_greater
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_allow_greater" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_allow_greater #-}

instance Method "set_allow_greater" GodotRange (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_allow_greater (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_is_greater_allowed
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "is_greater_allowed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_is_greater_allowed #-}

instance Method "is_greater_allowed" GodotRange (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_is_greater_allowed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_set_allow_lesser
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "set_allow_lesser" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_set_allow_lesser #-}

instance Method "set_allow_lesser" GodotRange (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_set_allow_lesser (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_is_lesser_allowed
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "is_lesser_allowed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_is_lesser_allowed #-}

instance Method "is_lesser_allowed" GodotRange (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_is_lesser_allowed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_share
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "share" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_share #-}

instance Method "share" GodotRange (GodotObject -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_share (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRange_unshare
  = unsafePerformIO $
      withCString "Range" $
        \ clsNamePtr ->
          withCString "unshare" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRange_unshare #-}

instance Method "unshare" GodotRange (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRange_unshare (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotScrollBar = GodotScrollBar GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotScrollBar where
        type BaseClass GodotScrollBar = GodotRange
        super = coerce
bindScrollBar__gui_input
  = unsafePerformIO $
      withCString "ScrollBar" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollBar__gui_input #-}

instance Method "_gui_input" GodotScrollBar
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollBar__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollBar_set_custom_step
  = unsafePerformIO $
      withCString "ScrollBar" $
        \ clsNamePtr ->
          withCString "set_custom_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollBar_set_custom_step #-}

instance Method "set_custom_step" GodotScrollBar (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollBar_set_custom_step (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollBar_get_custom_step
  = unsafePerformIO $
      withCString "ScrollBar" $
        \ clsNamePtr ->
          withCString "get_custom_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollBar_get_custom_step #-}

instance Method "get_custom_step" GodotScrollBar (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollBar_get_custom_step (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollBar__drag_node_input
  = unsafePerformIO $
      withCString "ScrollBar" $
        \ clsNamePtr ->
          withCString "_drag_node_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollBar__drag_node_input #-}

instance Method "_drag_node_input" GodotScrollBar
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollBar__drag_node_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollBar__drag_node_exit
  = unsafePerformIO $
      withCString "ScrollBar" $
        \ clsNamePtr ->
          withCString "_drag_node_exit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollBar__drag_node_exit #-}

instance Method "_drag_node_exit" GodotScrollBar (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollBar__drag_node_exit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotHScrollBar = GodotHScrollBar GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotHScrollBar where
        type BaseClass GodotHScrollBar = GodotScrollBar
        super = coerce

newtype GodotVScrollBar = GodotVScrollBar GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotVScrollBar where
        type BaseClass GodotVScrollBar = GodotScrollBar
        super = coerce

newtype GodotProgressBar = GodotProgressBar GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotProgressBar where
        type BaseClass GodotProgressBar = GodotRange
        super = coerce
bindProgressBar_set_percent_visible
  = unsafePerformIO $
      withCString "ProgressBar" $
        \ clsNamePtr ->
          withCString "set_percent_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProgressBar_set_percent_visible #-}

instance Method "set_percent_visible" GodotProgressBar
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProgressBar_set_percent_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProgressBar_is_percent_visible
  = unsafePerformIO $
      withCString "ProgressBar" $
        \ clsNamePtr ->
          withCString "is_percent_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProgressBar_is_percent_visible #-}

instance Method "is_percent_visible" GodotProgressBar (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProgressBar_is_percent_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSlider = GodotSlider GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotSlider where
        type BaseClass GodotSlider = GodotRange
        super = coerce
bindSlider_get_focus_mode
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "get_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_get_focus_mode #-}

instance Method "get_focus_mode" GodotSlider (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_get_focus_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_set_focus_mode
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "set_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_set_focus_mode #-}

instance Method "set_focus_mode" GodotSlider (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_set_focus_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider__gui_input
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider__gui_input #-}

instance Method "_gui_input" GodotSlider (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_set_ticks
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "set_ticks" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_set_ticks #-}

instance Method "set_ticks" GodotSlider (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_set_ticks (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_get_ticks
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "get_ticks" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_get_ticks #-}

instance Method "get_ticks" GodotSlider (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_get_ticks (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_get_ticks_on_borders
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "get_ticks_on_borders" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_get_ticks_on_borders #-}

instance Method "get_ticks_on_borders" GodotSlider (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_get_ticks_on_borders (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_set_ticks_on_borders
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "set_ticks_on_borders" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_set_ticks_on_borders #-}

instance Method "set_ticks_on_borders" GodotSlider (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_set_ticks_on_borders (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_set_editable
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "set_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_set_editable #-}

instance Method "set_editable" GodotSlider (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_set_editable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_is_editable
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "is_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_is_editable #-}

instance Method "is_editable" GodotSlider (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_is_editable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_set_scrollable
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "set_scrollable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_set_scrollable #-}

instance Method "set_scrollable" GodotSlider (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_set_scrollable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSlider_is_scrollable
  = unsafePerformIO $
      withCString "Slider" $
        \ clsNamePtr ->
          withCString "is_scrollable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSlider_is_scrollable #-}

instance Method "is_scrollable" GodotSlider (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSlider_is_scrollable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotHSlider = GodotHSlider GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotHSlider where
        type BaseClass GodotHSlider = GodotSlider
        super = coerce

newtype GodotVSlider = GodotVSlider GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotVSlider where
        type BaseClass GodotVSlider = GodotSlider
        super = coerce

newtype GodotPopup = GodotPopup GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotPopup where
        type BaseClass GodotPopup = GodotControl
        super = coerce
bindPopup_popup_centered
  = unsafePerformIO $
      withCString "Popup" $
        \ clsNamePtr ->
          withCString "popup_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopup_popup_centered #-}

instance Method "popup_centered" GodotPopup (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopup_popup_centered (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopup_popup_centered_ratio
  = unsafePerformIO $
      withCString "Popup" $
        \ clsNamePtr ->
          withCString "popup_centered_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopup_popup_centered_ratio #-}

instance Method "popup_centered_ratio" GodotPopup (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopup_popup_centered_ratio (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopup_popup_centered_minsize
  = unsafePerformIO $
      withCString "Popup" $
        \ clsNamePtr ->
          withCString "popup_centered_minsize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopup_popup_centered_minsize #-}

instance Method "popup_centered_minsize" GodotPopup
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopup_popup_centered_minsize
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopup_popup
  = unsafePerformIO $
      withCString "Popup" $
        \ clsNamePtr ->
          withCString "popup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopup_popup #-}

instance Method "popup" GodotPopup (GodotRect2 -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopup_popup (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopup_set_exclusive
  = unsafePerformIO $
      withCString "Popup" $
        \ clsNamePtr ->
          withCString "set_exclusive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopup_set_exclusive #-}

instance Method "set_exclusive" GodotPopup (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopup_set_exclusive (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopup_is_exclusive
  = unsafePerformIO $
      withCString "Popup" $
        \ clsNamePtr ->
          withCString "is_exclusive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopup_is_exclusive #-}

instance Method "is_exclusive" GodotPopup (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopup_is_exclusive (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPopupPanel = GodotPopupPanel GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotPopupPanel where
        type BaseClass GodotPopupPanel = GodotPopup
        super = coerce

newtype GodotMenuButton = GodotMenuButton GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotMenuButton where
        type BaseClass GodotMenuButton = GodotButton
        super = coerce
bindMenuButton_get_popup
  = unsafePerformIO $
      withCString "MenuButton" $
        \ clsNamePtr ->
          withCString "get_popup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMenuButton_get_popup #-}

instance Method "get_popup" GodotMenuButton (IO GodotPopupMenu)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMenuButton_get_popup (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMenuButton__unhandled_key_input
  = unsafePerformIO $
      withCString "MenuButton" $
        \ clsNamePtr ->
          withCString "_unhandled_key_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMenuButton__unhandled_key_input #-}

instance Method "_unhandled_key_input" GodotMenuButton
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMenuButton__unhandled_key_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMenuButton__set_items
  = unsafePerformIO $
      withCString "MenuButton" $
        \ clsNamePtr ->
          withCString "_set_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMenuButton__set_items #-}

instance Method "_set_items" GodotMenuButton (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMenuButton__set_items (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMenuButton__get_items
  = unsafePerformIO $
      withCString "MenuButton" $
        \ clsNamePtr ->
          withCString "_get_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMenuButton__get_items #-}

instance Method "_get_items" GodotMenuButton (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMenuButton__get_items (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMenuButton_set_disable_shortcuts
  = unsafePerformIO $
      withCString "MenuButton" $
        \ clsNamePtr ->
          withCString "set_disable_shortcuts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMenuButton_set_disable_shortcuts #-}

instance Method "set_disable_shortcuts" GodotMenuButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMenuButton_set_disable_shortcuts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCheckBox = GodotCheckBox GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotCheckBox where
        type BaseClass GodotCheckBox = GodotButton
        super = coerce

newtype GodotCheckButton = GodotCheckButton GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotCheckButton where
        type BaseClass GodotCheckButton = GodotButton
        super = coerce

newtype GodotToolButton = GodotToolButton GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotToolButton where
        type BaseClass GodotToolButton = GodotButton
        super = coerce

newtype GodotLinkButton = GodotLinkButton GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotLinkButton where
        type BaseClass GodotLinkButton = GodotBaseButton
        super = coerce
bindLinkButton_set_text
  = unsafePerformIO $
      withCString "LinkButton" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLinkButton_set_text #-}

instance Method "set_text" GodotLinkButton (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLinkButton_set_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLinkButton_get_text
  = unsafePerformIO $
      withCString "LinkButton" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLinkButton_get_text #-}

instance Method "get_text" GodotLinkButton (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLinkButton_get_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLinkButton_set_underline_mode
  = unsafePerformIO $
      withCString "LinkButton" $
        \ clsNamePtr ->
          withCString "set_underline_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLinkButton_set_underline_mode #-}

instance Method "set_underline_mode" GodotLinkButton (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLinkButton_set_underline_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLinkButton_get_underline_mode
  = unsafePerformIO $
      withCString "LinkButton" $
        \ clsNamePtr ->
          withCString "get_underline_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLinkButton_get_underline_mode #-}

instance Method "get_underline_mode" GodotLinkButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLinkButton_get_underline_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPanel = GodotPanel GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotPanel where
        type BaseClass GodotPanel = GodotControl
        super = coerce

newtype GodotTextureRect = GodotTextureRect GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotTextureRect where
        type BaseClass GodotTextureRect = GodotControl
        super = coerce
bindTextureRect_set_texture
  = unsafePerformIO $
      withCString "TextureRect" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureRect_set_texture #-}

instance Method "set_texture" GodotTextureRect
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureRect_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureRect_get_texture
  = unsafePerformIO $
      withCString "TextureRect" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureRect_get_texture #-}

instance Method "get_texture" GodotTextureRect (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureRect_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureRect_set_expand
  = unsafePerformIO $
      withCString "TextureRect" $
        \ clsNamePtr ->
          withCString "set_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureRect_set_expand #-}

instance Method "set_expand" GodotTextureRect (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureRect_set_expand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureRect_has_expand
  = unsafePerformIO $
      withCString "TextureRect" $
        \ clsNamePtr ->
          withCString "has_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureRect_has_expand #-}

instance Method "has_expand" GodotTextureRect (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureRect_has_expand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureRect_set_stretch_mode
  = unsafePerformIO $
      withCString "TextureRect" $
        \ clsNamePtr ->
          withCString "set_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureRect_set_stretch_mode #-}

instance Method "set_stretch_mode" GodotTextureRect (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureRect_set_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureRect_get_stretch_mode
  = unsafePerformIO $
      withCString "TextureRect" $
        \ clsNamePtr ->
          withCString "get_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureRect_get_stretch_mode #-}

instance Method "get_stretch_mode" GodotTextureRect (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureRect_get_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotColorRect = GodotColorRect GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotColorRect where
        type BaseClass GodotColorRect = GodotControl
        super = coerce
bindColorRect_set_frame_color
  = unsafePerformIO $
      withCString "ColorRect" $
        \ clsNamePtr ->
          withCString "set_frame_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorRect_set_frame_color #-}

instance Method "set_frame_color" GodotColorRect
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorRect_set_frame_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorRect_get_frame_color
  = unsafePerformIO $
      withCString "ColorRect" $
        \ clsNamePtr ->
          withCString "get_frame_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorRect_get_frame_color #-}

instance Method "get_frame_color" GodotColorRect (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorRect_get_frame_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNinePatchRect = GodotNinePatchRect GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotNinePatchRect where
        type BaseClass GodotNinePatchRect = GodotControl
        super = coerce
bindNinePatchRect_set_texture
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_set_texture #-}

instance Method "set_texture" GodotNinePatchRect
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_get_texture
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_get_texture #-}

instance Method "get_texture" GodotNinePatchRect (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_set_patch_margin
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "set_patch_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_set_patch_margin #-}

instance Method "set_patch_margin" GodotNinePatchRect
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_set_patch_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_get_patch_margin
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "get_patch_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_get_patch_margin #-}

instance Method "get_patch_margin" GodotNinePatchRect
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_get_patch_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_set_region_rect
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "set_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_set_region_rect #-}

instance Method "set_region_rect" GodotNinePatchRect
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_set_region_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_get_region_rect
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "get_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_get_region_rect #-}

instance Method "get_region_rect" GodotNinePatchRect
           (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_get_region_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_set_draw_center
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "set_draw_center" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_set_draw_center #-}

instance Method "set_draw_center" GodotNinePatchRect
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_set_draw_center
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_is_draw_center_enabled
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "is_draw_center_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_is_draw_center_enabled #-}

instance Method "is_draw_center_enabled" GodotNinePatchRect
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_is_draw_center_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_set_h_axis_stretch_mode
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "set_h_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_set_h_axis_stretch_mode #-}

instance Method "set_h_axis_stretch_mode" GodotNinePatchRect
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_set_h_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_get_h_axis_stretch_mode
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "get_h_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_get_h_axis_stretch_mode #-}

instance Method "get_h_axis_stretch_mode" GodotNinePatchRect
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_get_h_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_set_v_axis_stretch_mode
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "set_v_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_set_v_axis_stretch_mode #-}

instance Method "set_v_axis_stretch_mode" GodotNinePatchRect
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_set_v_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNinePatchRect_get_v_axis_stretch_mode
  = unsafePerformIO $
      withCString "NinePatchRect" $
        \ clsNamePtr ->
          withCString "get_v_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNinePatchRect_get_v_axis_stretch_mode #-}

instance Method "get_v_axis_stretch_mode" GodotNinePatchRect
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNinePatchRect_get_v_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotContainer = GodotContainer GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotContainer where
        type BaseClass GodotContainer = GodotControl
        super = coerce
bindContainer__sort_children
  = unsafePerformIO $
      withCString "Container" $
        \ clsNamePtr ->
          withCString "_sort_children" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindContainer__sort_children #-}

instance Method "_sort_children" GodotContainer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindContainer__sort_children (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindContainer__child_minsize_changed
  = unsafePerformIO $
      withCString "Container" $
        \ clsNamePtr ->
          withCString "_child_minsize_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindContainer__child_minsize_changed #-}

instance Method "_child_minsize_changed" GodotContainer (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindContainer__child_minsize_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindContainer_queue_sort
  = unsafePerformIO $
      withCString "Container" $
        \ clsNamePtr ->
          withCString "queue_sort" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindContainer_queue_sort #-}

instance Method "queue_sort" GodotContainer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindContainer_queue_sort (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindContainer_fit_child_in_rect
  = unsafePerformIO $
      withCString "Container" $
        \ clsNamePtr ->
          withCString "fit_child_in_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindContainer_fit_child_in_rect #-}

instance Method "fit_child_in_rect" GodotContainer
           (GodotObject -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindContainer_fit_child_in_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTabContainer = GodotTabContainer GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotTabContainer where
        type BaseClass GodotTabContainer = GodotContainer
        super = coerce
bindTabContainer__gui_input
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer__gui_input #-}

instance Method "_gui_input" GodotTabContainer
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer__gui_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_tab_count
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_tab_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_tab_count #-}

instance Method "get_tab_count" GodotTabContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_tab_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_current_tab
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_current_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_current_tab #-}

instance Method "set_current_tab" GodotTabContainer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_current_tab
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_current_tab
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_current_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_current_tab #-}

instance Method "get_current_tab" GodotTabContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_current_tab
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_previous_tab
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_previous_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_previous_tab #-}

instance Method "get_previous_tab" GodotTabContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_previous_tab
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_current_tab_control
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_current_tab_control" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_current_tab_control #-}

instance Method "get_current_tab_control" GodotTabContainer
           (IO GodotControl)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_current_tab_control
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_tab_control
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_tab_control" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_tab_control #-}

instance Method "get_tab_control" GodotTabContainer
           (Int -> IO GodotControl)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_tab_control
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_tab_align
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_tab_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_tab_align #-}

instance Method "set_tab_align" GodotTabContainer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_tab_align (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_tab_align
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_tab_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_tab_align #-}

instance Method "get_tab_align" GodotTabContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_tab_align (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_tabs_visible
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_tabs_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_tabs_visible #-}

instance Method "set_tabs_visible" GodotTabContainer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_tabs_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_are_tabs_visible
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "are_tabs_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_are_tabs_visible #-}

instance Method "are_tabs_visible" GodotTabContainer (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_are_tabs_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_tab_title
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_tab_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_tab_title #-}

instance Method "set_tab_title" GodotTabContainer
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_tab_title (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_tab_title
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_tab_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_tab_title #-}

instance Method "get_tab_title" GodotTabContainer
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_tab_title (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_tab_icon
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_tab_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_tab_icon #-}

instance Method "set_tab_icon" GodotTabContainer
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_tab_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_tab_icon
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_tab_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_tab_icon #-}

instance Method "get_tab_icon" GodotTabContainer
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_tab_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_tab_disabled
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_tab_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_tab_disabled #-}

instance Method "set_tab_disabled" GodotTabContainer
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_tab_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_tab_disabled
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_tab_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_tab_disabled #-}

instance Method "get_tab_disabled" GodotTabContainer
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_tab_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_popup
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_popup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_popup #-}

instance Method "set_popup" GodotTabContainer
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_popup (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_popup
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_popup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_popup #-}

instance Method "get_popup" GodotTabContainer (IO GodotPopup) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_popup (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_drag_to_rearrange_enabled
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_drag_to_rearrange_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_drag_to_rearrange_enabled #-}

instance Method "set_drag_to_rearrange_enabled" GodotTabContainer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTabContainer_set_drag_to_rearrange_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_drag_to_rearrange_enabled
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_drag_to_rearrange_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_drag_to_rearrange_enabled #-}

instance Method "get_drag_to_rearrange_enabled" GodotTabContainer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTabContainer_get_drag_to_rearrange_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_set_tabs_rearrange_group
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "set_tabs_rearrange_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_set_tabs_rearrange_group #-}

instance Method "set_tabs_rearrange_group" GodotTabContainer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_set_tabs_rearrange_group
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer_get_tabs_rearrange_group
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "get_tabs_rearrange_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer_get_tabs_rearrange_group #-}

instance Method "get_tabs_rearrange_group" GodotTabContainer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer_get_tabs_rearrange_group
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer__child_renamed_callback
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "_child_renamed_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer__child_renamed_callback #-}

instance Method "_child_renamed_callback" GodotTabContainer (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer__child_renamed_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer__on_theme_changed
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "_on_theme_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer__on_theme_changed #-}

instance Method "_on_theme_changed" GodotTabContainer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer__on_theme_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabContainer__update_current_tab
  = unsafePerformIO $
      withCString "TabContainer" $
        \ clsNamePtr ->
          withCString "_update_current_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabContainer__update_current_tab #-}

instance Method "_update_current_tab" GodotTabContainer (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabContainer__update_current_tab
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTabs = GodotTabs GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotTabs where
        type BaseClass GodotTabs = GodotControl
        super = coerce
bindTabs__gui_input
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs__gui_input #-}

instance Method "_gui_input" GodotTabs (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs__gui_input (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs__update_hover
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "_update_hover" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs__update_hover #-}

instance Method "_update_hover" GodotTabs (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs__update_hover (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_count
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_count #-}

instance Method "get_tab_count" GodotTabs (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_count (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_current_tab
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_current_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_current_tab #-}

instance Method "set_current_tab" GodotTabs (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_current_tab (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_current_tab
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_current_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_current_tab #-}

instance Method "get_current_tab" GodotTabs (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_current_tab (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_tab_title
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_tab_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_tab_title #-}

instance Method "set_tab_title" GodotTabs
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_tab_title (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_title
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_title #-}

instance Method "get_tab_title" GodotTabs (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_title (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_tab_icon
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_tab_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_tab_icon #-}

instance Method "set_tab_icon" GodotTabs
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_tab_icon (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_icon
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_icon #-}

instance Method "get_tab_icon" GodotTabs (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_icon (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_tab_disabled
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_tab_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_tab_disabled #-}

instance Method "set_tab_disabled" GodotTabs (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_tab_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_disabled
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_disabled #-}

instance Method "get_tab_disabled" GodotTabs (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_remove_tab
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "remove_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_remove_tab #-}

instance Method "remove_tab" GodotTabs (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_remove_tab (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_add_tab
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "add_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_add_tab #-}

instance Method "add_tab" GodotTabs
           (GodotString -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_add_tab (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_tab_align
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_tab_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_tab_align #-}

instance Method "set_tab_align" GodotTabs (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_tab_align (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_align
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_align #-}

instance Method "get_tab_align" GodotTabs (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_align (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_offset
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_offset #-}

instance Method "get_tab_offset" GodotTabs (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_offset_buttons_visible
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_offset_buttons_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_offset_buttons_visible #-}

instance Method "get_offset_buttons_visible" GodotTabs (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_offset_buttons_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_ensure_tab_visible
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "ensure_tab_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_ensure_tab_visible #-}

instance Method "ensure_tab_visible" GodotTabs (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_ensure_tab_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_rect
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_rect #-}

instance Method "get_tab_rect" GodotTabs (Int -> IO GodotRect2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_rect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_move_tab
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "move_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_move_tab #-}

instance Method "move_tab" GodotTabs (Int -> Int -> IO ()) where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_move_tab (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_tab_close_display_policy
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_tab_close_display_policy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_tab_close_display_policy #-}

instance Method "set_tab_close_display_policy" GodotTabs
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_tab_close_display_policy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tab_close_display_policy
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tab_close_display_policy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tab_close_display_policy #-}

instance Method "get_tab_close_display_policy" GodotTabs (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tab_close_display_policy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_scrolling_enabled
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_scrolling_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_scrolling_enabled #-}

instance Method "set_scrolling_enabled" GodotTabs (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_scrolling_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_scrolling_enabled
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_scrolling_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_scrolling_enabled #-}

instance Method "get_scrolling_enabled" GodotTabs (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_scrolling_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_drag_to_rearrange_enabled
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_drag_to_rearrange_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_drag_to_rearrange_enabled #-}

instance Method "set_drag_to_rearrange_enabled" GodotTabs
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_drag_to_rearrange_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_drag_to_rearrange_enabled
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_drag_to_rearrange_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_drag_to_rearrange_enabled #-}

instance Method "get_drag_to_rearrange_enabled" GodotTabs (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_drag_to_rearrange_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_tabs_rearrange_group
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_tabs_rearrange_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_tabs_rearrange_group #-}

instance Method "set_tabs_rearrange_group" GodotTabs (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_tabs_rearrange_group
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_tabs_rearrange_group
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_tabs_rearrange_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_tabs_rearrange_group #-}

instance Method "get_tabs_rearrange_group" GodotTabs (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_tabs_rearrange_group
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_set_select_with_rmb
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "set_select_with_rmb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_set_select_with_rmb #-}

instance Method "set_select_with_rmb" GodotTabs (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_set_select_with_rmb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTabs_get_select_with_rmb
  = unsafePerformIO $
      withCString "Tabs" $
        \ clsNamePtr ->
          withCString "get_select_with_rmb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTabs_get_select_with_rmb #-}

instance Method "get_select_with_rmb" GodotTabs (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTabs_get_select_with_rmb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSeparator = GodotSeparator GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotSeparator where
        type BaseClass GodotSeparator = GodotControl
        super = coerce

newtype GodotHSeparator = GodotHSeparator GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotHSeparator where
        type BaseClass GodotHSeparator = GodotSeparator
        super = coerce

newtype GodotVSeparator = GodotVSeparator GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotVSeparator where
        type BaseClass GodotVSeparator = GodotSeparator
        super = coerce

newtype GodotTextureButton = GodotTextureButton GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotTextureButton where
        type BaseClass GodotTextureButton = GodotBaseButton
        super = coerce
bindTextureButton_set_normal_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_normal_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_normal_texture #-}

instance Method "set_normal_texture" GodotTextureButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_normal_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_set_pressed_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_pressed_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_pressed_texture #-}

instance Method "set_pressed_texture" GodotTextureButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_pressed_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_set_hover_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_hover_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_hover_texture #-}

instance Method "set_hover_texture" GodotTextureButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_hover_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_set_disabled_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_disabled_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_disabled_texture #-}

instance Method "set_disabled_texture" GodotTextureButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_disabled_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_set_focused_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_focused_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_focused_texture #-}

instance Method "set_focused_texture" GodotTextureButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_focused_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_set_click_mask
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_click_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_click_mask #-}

instance Method "set_click_mask" GodotTextureButton
           (GodotBitMap -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_click_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_set_expand
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_expand #-}

instance Method "set_expand" GodotTextureButton (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_expand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_set_stretch_mode
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "set_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_set_stretch_mode #-}

instance Method "set_stretch_mode" GodotTextureButton
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_set_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_normal_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_normal_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_normal_texture #-}

instance Method "get_normal_texture" GodotTextureButton
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_normal_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_pressed_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_pressed_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_pressed_texture #-}

instance Method "get_pressed_texture" GodotTextureButton
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_pressed_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_hover_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_hover_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_hover_texture #-}

instance Method "get_hover_texture" GodotTextureButton
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_hover_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_disabled_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_disabled_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_disabled_texture #-}

instance Method "get_disabled_texture" GodotTextureButton
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_disabled_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_focused_texture
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_focused_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_focused_texture #-}

instance Method "get_focused_texture" GodotTextureButton
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_focused_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_click_mask
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_click_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_click_mask #-}

instance Method "get_click_mask" GodotTextureButton
           (IO GodotBitMap)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_click_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_expand
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_expand #-}

instance Method "get_expand" GodotTextureButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_expand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureButton_get_stretch_mode
  = unsafePerformIO $
      withCString "TextureButton" $
        \ clsNamePtr ->
          withCString "get_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureButton_get_stretch_mode #-}

instance Method "get_stretch_mode" GodotTextureButton (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureButton_get_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBitMap = GodotBitMap GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotBitMap where
        type BaseClass GodotBitMap = GodotResource
        super = coerce
bindBitMap_create
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_create #-}

instance Method "create" GodotBitMap (GodotVector2 -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_create (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_create_from_image_alpha
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "create_from_image_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_create_from_image_alpha #-}

instance Method "create_from_image_alpha" GodotBitMap
           (GodotImage -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_create_from_image_alpha
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_set_bit
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "set_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_set_bit #-}

instance Method "set_bit" GodotBitMap
           (GodotVector2 -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_set_bit (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_get_bit
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "get_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_get_bit #-}

instance Method "get_bit" GodotBitMap (GodotVector2 -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_get_bit (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_set_bit_rect
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "set_bit_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_set_bit_rect #-}

instance Method "set_bit_rect" GodotBitMap
           (GodotRect2 -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_set_bit_rect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_get_true_bit_count
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "get_true_bit_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_get_true_bit_count #-}

instance Method "get_true_bit_count" GodotBitMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_get_true_bit_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_get_size
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_get_size #-}

instance Method "get_size" GodotBitMap (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_get_size (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap__set_data
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap__set_data #-}

instance Method "_set_data" GodotBitMap (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap__set_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap__get_data
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap__get_data #-}

instance Method "_get_data" GodotBitMap (IO GodotDictionary) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap__get_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_grow_mask
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "grow_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_grow_mask #-}

instance Method "grow_mask" GodotBitMap
           (Int -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_grow_mask (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitMap_opaque_to_polygons
  = unsafePerformIO $
      withCString "BitMap" $
        \ clsNamePtr ->
          withCString "opaque_to_polygons" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitMap_opaque_to_polygons #-}

instance Method "opaque_to_polygons" GodotBitMap
           (GodotRect2 -> Float -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitMap_opaque_to_polygons (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBoxContainer = GodotBoxContainer GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotBoxContainer where
        type BaseClass GodotBoxContainer = GodotContainer
        super = coerce
bindBoxContainer_add_spacer
  = unsafePerformIO $
      withCString "BoxContainer" $
        \ clsNamePtr ->
          withCString "add_spacer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBoxContainer_add_spacer #-}

instance Method "add_spacer" GodotBoxContainer (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBoxContainer_add_spacer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBoxContainer_get_alignment
  = unsafePerformIO $
      withCString "BoxContainer" $
        \ clsNamePtr ->
          withCString "get_alignment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBoxContainer_get_alignment #-}

instance Method "get_alignment" GodotBoxContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBoxContainer_get_alignment (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBoxContainer_set_alignment
  = unsafePerformIO $
      withCString "BoxContainer" $
        \ clsNamePtr ->
          withCString "set_alignment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBoxContainer_set_alignment #-}

instance Method "set_alignment" GodotBoxContainer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBoxContainer_set_alignment (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotHBoxContainer = GodotHBoxContainer GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotHBoxContainer where
        type BaseClass GodotHBoxContainer = GodotBoxContainer
        super = coerce

newtype GodotVBoxContainer = GodotVBoxContainer GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotVBoxContainer where
        type BaseClass GodotVBoxContainer = GodotBoxContainer
        super = coerce

newtype GodotGridContainer = GodotGridContainer GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotGridContainer where
        type BaseClass GodotGridContainer = GodotContainer
        super = coerce
bindGridContainer_set_columns
  = unsafePerformIO $
      withCString "GridContainer" $
        \ clsNamePtr ->
          withCString "set_columns" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridContainer_set_columns #-}

instance Method "set_columns" GodotGridContainer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridContainer_set_columns (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridContainer_get_columns
  = unsafePerformIO $
      withCString "GridContainer" $
        \ clsNamePtr ->
          withCString "get_columns" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridContainer_get_columns #-}

instance Method "get_columns" GodotGridContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridContainer_get_columns (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCenterContainer = GodotCenterContainer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotCenterContainer where
        type BaseClass GodotCenterContainer = GodotContainer
        super = coerce
bindCenterContainer_set_use_top_left
  = unsafePerformIO $
      withCString "CenterContainer" $
        \ clsNamePtr ->
          withCString "set_use_top_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCenterContainer_set_use_top_left #-}

instance Method "set_use_top_left" GodotCenterContainer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCenterContainer_set_use_top_left
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCenterContainer_is_using_top_left
  = unsafePerformIO $
      withCString "CenterContainer" $
        \ clsNamePtr ->
          withCString "is_using_top_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCenterContainer_is_using_top_left #-}

instance Method "is_using_top_left" GodotCenterContainer (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCenterContainer_is_using_top_left
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotScrollContainer = GodotScrollContainer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotScrollContainer where
        type BaseClass GodotScrollContainer = GodotContainer
        super = coerce
bindScrollContainer__scroll_moved
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "_scroll_moved" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer__scroll_moved #-}

instance Method "_scroll_moved" GodotScrollContainer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer__scroll_moved
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer__gui_input
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer__gui_input #-}

instance Method "_gui_input" GodotScrollContainer
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer__gui_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_set_enable_h_scroll
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "set_enable_h_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_set_enable_h_scroll #-}

instance Method "set_enable_h_scroll" GodotScrollContainer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_set_enable_h_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_is_h_scroll_enabled
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "is_h_scroll_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_is_h_scroll_enabled #-}

instance Method "is_h_scroll_enabled" GodotScrollContainer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_is_h_scroll_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_set_enable_v_scroll
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "set_enable_v_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_set_enable_v_scroll #-}

instance Method "set_enable_v_scroll" GodotScrollContainer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_set_enable_v_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_is_v_scroll_enabled
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "is_v_scroll_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_is_v_scroll_enabled #-}

instance Method "is_v_scroll_enabled" GodotScrollContainer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_is_v_scroll_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer__update_scrollbar_position
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "_update_scrollbar_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer__update_scrollbar_position #-}

instance Method "_update_scrollbar_position" GodotScrollContainer
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindScrollContainer__update_scrollbar_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_set_h_scroll
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "set_h_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_set_h_scroll #-}

instance Method "set_h_scroll" GodotScrollContainer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_set_h_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_get_h_scroll
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "get_h_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_get_h_scroll #-}

instance Method "get_h_scroll" GodotScrollContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_get_h_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_set_v_scroll
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "set_v_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_set_v_scroll #-}

instance Method "set_v_scroll" GodotScrollContainer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_set_v_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_get_v_scroll
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "get_v_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_get_v_scroll #-}

instance Method "get_v_scroll" GodotScrollContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_get_v_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_set_deadzone
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "set_deadzone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_set_deadzone #-}

instance Method "set_deadzone" GodotScrollContainer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_set_deadzone
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_get_deadzone
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "get_deadzone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_get_deadzone #-}

instance Method "get_deadzone" GodotScrollContainer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_get_deadzone
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_get_h_scrollbar
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "get_h_scrollbar" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_get_h_scrollbar #-}

instance Method "get_h_scrollbar" GodotScrollContainer
           (IO GodotHScrollBar)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_get_h_scrollbar
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScrollContainer_get_v_scrollbar
  = unsafePerformIO $
      withCString "ScrollContainer" $
        \ clsNamePtr ->
          withCString "get_v_scrollbar" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScrollContainer_get_v_scrollbar #-}

instance Method "get_v_scrollbar" GodotScrollContainer
           (IO GodotVScrollBar)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScrollContainer_get_v_scrollbar
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPanelContainer = GodotPanelContainer GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotPanelContainer where
        type BaseClass GodotPanelContainer = GodotContainer
        super = coerce

newtype GodotTextureProgress = GodotTextureProgress GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotTextureProgress where
        type BaseClass GodotTextureProgress = GodotRange
        super = coerce
bindTextureProgress_set_under_texture
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_under_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_under_texture #-}

instance Method "set_under_texture" GodotTextureProgress
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_under_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_under_texture
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_under_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_under_texture #-}

instance Method "get_under_texture" GodotTextureProgress
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_under_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_progress_texture
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_progress_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_progress_texture #-}

instance Method "set_progress_texture" GodotTextureProgress
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_progress_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_progress_texture
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_progress_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_progress_texture #-}

instance Method "get_progress_texture" GodotTextureProgress
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_progress_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_over_texture
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_over_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_over_texture #-}

instance Method "set_over_texture" GodotTextureProgress
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_over_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_over_texture
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_over_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_over_texture #-}

instance Method "get_over_texture" GodotTextureProgress
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_over_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_fill_mode
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_fill_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_fill_mode #-}

instance Method "set_fill_mode" GodotTextureProgress (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_fill_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_fill_mode
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_fill_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_fill_mode #-}

instance Method "get_fill_mode" GodotTextureProgress (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_fill_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_tint_under
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_tint_under" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_tint_under #-}

instance Method "set_tint_under" GodotTextureProgress
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_tint_under
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_tint_under
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_tint_under" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_tint_under #-}

instance Method "get_tint_under" GodotTextureProgress
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_tint_under
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_tint_progress
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_tint_progress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_tint_progress #-}

instance Method "set_tint_progress" GodotTextureProgress
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_tint_progress
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_tint_progress
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_tint_progress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_tint_progress #-}

instance Method "get_tint_progress" GodotTextureProgress
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_tint_progress
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_tint_over
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_tint_over" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_tint_over #-}

instance Method "set_tint_over" GodotTextureProgress
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_tint_over
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_tint_over
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_tint_over" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_tint_over #-}

instance Method "get_tint_over" GodotTextureProgress
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_tint_over
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_radial_initial_angle
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_radial_initial_angle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_radial_initial_angle #-}

instance Method "set_radial_initial_angle" GodotTextureProgress
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_radial_initial_angle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_radial_initial_angle
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_radial_initial_angle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_radial_initial_angle #-}

instance Method "get_radial_initial_angle" GodotTextureProgress
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_radial_initial_angle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_radial_center_offset
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_radial_center_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_radial_center_offset #-}

instance Method "set_radial_center_offset" GodotTextureProgress
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_radial_center_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_radial_center_offset
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_radial_center_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_radial_center_offset #-}

instance Method "get_radial_center_offset" GodotTextureProgress
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_radial_center_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_fill_degrees
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_fill_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_fill_degrees #-}

instance Method "set_fill_degrees" GodotTextureProgress
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_fill_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_fill_degrees
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_fill_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_fill_degrees #-}

instance Method "get_fill_degrees" GodotTextureProgress (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_fill_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_stretch_margin
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_stretch_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_stretch_margin #-}

instance Method "set_stretch_margin" GodotTextureProgress
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_stretch_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_stretch_margin
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_stretch_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_stretch_margin #-}

instance Method "get_stretch_margin" GodotTextureProgress
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_stretch_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_set_nine_patch_stretch
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "set_nine_patch_stretch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_set_nine_patch_stretch #-}

instance Method "set_nine_patch_stretch" GodotTextureProgress
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_set_nine_patch_stretch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureProgress_get_nine_patch_stretch
  = unsafePerformIO $
      withCString "TextureProgress" $
        \ clsNamePtr ->
          withCString "get_nine_patch_stretch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureProgress_get_nine_patch_stretch #-}

instance Method "get_nine_patch_stretch" GodotTextureProgress
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureProgress_get_nine_patch_stretch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotItemList = GodotItemList GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotItemList where
        type BaseClass GodotItemList = GodotControl
        super = coerce
bindItemList_add_item
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "add_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_add_item #-}

instance Method "add_item" GodotItemList
           (GodotString -> GodotTexture -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_add_item (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_add_icon_item
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "add_icon_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_add_icon_item #-}

instance Method "add_icon_item" GodotItemList
           (GodotTexture -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_add_icon_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_text
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_text #-}

instance Method "set_item_text" GodotItemList
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_text
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_text #-}

instance Method "get_item_text" GodotItemList
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_icon
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_icon #-}

instance Method "set_item_icon" GodotItemList
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_icon
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_icon #-}

instance Method "get_item_icon" GodotItemList
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_icon_region
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_icon_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_icon_region #-}

instance Method "set_item_icon_region" GodotItemList
           (Int -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_icon_region
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_icon_region
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_icon_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_icon_region #-}

instance Method "get_item_icon_region" GodotItemList
           (Int -> IO GodotRect2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_icon_region
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_icon_modulate
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_icon_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_icon_modulate #-}

instance Method "set_item_icon_modulate" GodotItemList
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_icon_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_icon_modulate
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_icon_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_icon_modulate #-}

instance Method "get_item_icon_modulate" GodotItemList
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_icon_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_selectable
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_selectable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_selectable #-}

instance Method "set_item_selectable" GodotItemList
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_selectable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_is_item_selectable
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "is_item_selectable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_is_item_selectable #-}

instance Method "is_item_selectable" GodotItemList (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_is_item_selectable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_disabled
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_disabled #-}

instance Method "set_item_disabled" GodotItemList
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_is_item_disabled
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "is_item_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_is_item_disabled #-}

instance Method "is_item_disabled" GodotItemList (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_is_item_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_metadata
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_metadata #-}

instance Method "set_item_metadata" GodotItemList
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_metadata (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_metadata
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_metadata #-}

instance Method "get_item_metadata" GodotItemList
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_metadata (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_custom_bg_color
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_custom_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_custom_bg_color #-}

instance Method "set_item_custom_bg_color" GodotItemList
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_custom_bg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_custom_bg_color
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_custom_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_custom_bg_color #-}

instance Method "get_item_custom_bg_color" GodotItemList
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_custom_bg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_custom_fg_color
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_custom_fg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_custom_fg_color #-}

instance Method "set_item_custom_fg_color" GodotItemList
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_custom_fg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_custom_fg_color
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_custom_fg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_custom_fg_color #-}

instance Method "get_item_custom_fg_color" GodotItemList
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_custom_fg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_tooltip_enabled
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_tooltip_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_tooltip_enabled #-}

instance Method "set_item_tooltip_enabled" GodotItemList
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_tooltip_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_is_item_tooltip_enabled
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "is_item_tooltip_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_is_item_tooltip_enabled #-}

instance Method "is_item_tooltip_enabled" GodotItemList
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_is_item_tooltip_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_item_tooltip
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_item_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_item_tooltip #-}

instance Method "set_item_tooltip" GodotItemList
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_item_tooltip (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_tooltip
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_tooltip #-}

instance Method "get_item_tooltip" GodotItemList
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_tooltip (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_select
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_select #-}

instance Method "select" GodotItemList (Int -> Bool -> IO ()) where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_select (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_unselect
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "unselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_unselect #-}

instance Method "unselect" GodotItemList (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_unselect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_unselect_all
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "unselect_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_unselect_all #-}

instance Method "unselect_all" GodotItemList (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_unselect_all (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_is_selected
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "is_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_is_selected #-}

instance Method "is_selected" GodotItemList (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_is_selected (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_selected_items
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_selected_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_selected_items #-}

instance Method "get_selected_items" GodotItemList
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_selected_items (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_move_item
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "move_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_move_item #-}

instance Method "move_item" GodotItemList (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_move_item (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_count
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_count #-}

instance Method "get_item_count" GodotItemList (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_remove_item
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "remove_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_remove_item #-}

instance Method "remove_item" GodotItemList (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_remove_item (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_clear
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_clear #-}

instance Method "clear" GodotItemList (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_sort_items_by_text
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "sort_items_by_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_sort_items_by_text #-}

instance Method "sort_items_by_text" GodotItemList (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_sort_items_by_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_fixed_column_width
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_fixed_column_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_fixed_column_width #-}

instance Method "set_fixed_column_width" GodotItemList
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_fixed_column_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_fixed_column_width
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_fixed_column_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_fixed_column_width #-}

instance Method "get_fixed_column_width" GodotItemList (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_fixed_column_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_same_column_width
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_same_column_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_same_column_width #-}

instance Method "set_same_column_width" GodotItemList
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_same_column_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_is_same_column_width
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "is_same_column_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_is_same_column_width #-}

instance Method "is_same_column_width" GodotItemList (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_is_same_column_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_max_text_lines
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_max_text_lines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_max_text_lines #-}

instance Method "set_max_text_lines" GodotItemList (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_max_text_lines (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_max_text_lines
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_max_text_lines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_max_text_lines #-}

instance Method "get_max_text_lines" GodotItemList (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_max_text_lines (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_max_columns
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_max_columns" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_max_columns #-}

instance Method "set_max_columns" GodotItemList (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_max_columns (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_max_columns
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_max_columns" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_max_columns #-}

instance Method "get_max_columns" GodotItemList (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_max_columns (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_select_mode
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_select_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_select_mode #-}

instance Method "set_select_mode" GodotItemList (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_select_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_select_mode
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_select_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_select_mode #-}

instance Method "get_select_mode" GodotItemList (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_select_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_icon_mode
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_icon_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_icon_mode #-}

instance Method "set_icon_mode" GodotItemList (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_icon_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_icon_mode
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_icon_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_icon_mode #-}

instance Method "get_icon_mode" GodotItemList (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_icon_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_fixed_icon_size
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_fixed_icon_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_fixed_icon_size #-}

instance Method "set_fixed_icon_size" GodotItemList
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_fixed_icon_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_fixed_icon_size
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_fixed_icon_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_fixed_icon_size #-}

instance Method "get_fixed_icon_size" GodotItemList
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_fixed_icon_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_icon_scale
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_icon_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_icon_scale #-}

instance Method "set_icon_scale" GodotItemList (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_icon_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_icon_scale
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_icon_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_icon_scale #-}

instance Method "get_icon_scale" GodotItemList (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_icon_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_allow_rmb_select
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_allow_rmb_select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_allow_rmb_select #-}

instance Method "set_allow_rmb_select" GodotItemList
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_allow_rmb_select
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_allow_rmb_select
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_allow_rmb_select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_allow_rmb_select #-}

instance Method "get_allow_rmb_select" GodotItemList (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_allow_rmb_select
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_allow_reselect
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_allow_reselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_allow_reselect #-}

instance Method "set_allow_reselect" GodotItemList (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_allow_reselect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_allow_reselect
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_allow_reselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_allow_reselect #-}

instance Method "get_allow_reselect" GodotItemList (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_allow_reselect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_set_auto_height
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "set_auto_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_set_auto_height #-}

instance Method "set_auto_height" GodotItemList (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_set_auto_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_has_auto_height
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "has_auto_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_has_auto_height #-}

instance Method "has_auto_height" GodotItemList (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_has_auto_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_is_anything_selected
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "is_anything_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_is_anything_selected #-}

instance Method "is_anything_selected" GodotItemList (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_is_anything_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_item_at_position
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_item_at_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_item_at_position #-}

instance Method "get_item_at_position" GodotItemList
           (GodotVector2 -> Bool -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_item_at_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_ensure_current_is_visible
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "ensure_current_is_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_ensure_current_is_visible #-}

instance Method "ensure_current_is_visible" GodotItemList (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_ensure_current_is_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList_get_v_scroll
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "get_v_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList_get_v_scroll #-}

instance Method "get_v_scroll" GodotItemList (IO GodotVScrollBar)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList_get_v_scroll (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList__scroll_changed
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "_scroll_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList__scroll_changed #-}

instance Method "_scroll_changed" GodotItemList (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList__scroll_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList__gui_input
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList__gui_input #-}

instance Method "_gui_input" GodotItemList
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList__set_items
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "_set_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList__set_items #-}

instance Method "_set_items" GodotItemList (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList__set_items (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindItemList__get_items
  = unsafePerformIO $
      withCString "ItemList" $
        \ clsNamePtr ->
          withCString "_get_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindItemList__get_items #-}

instance Method "_get_items" GodotItemList (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindItemList__get_items (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotLineEdit = GodotLineEdit GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotLineEdit where
        type BaseClass GodotLineEdit = GodotControl
        super = coerce
bindLineEdit_get_focus_mode
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_focus_mode #-}

instance Method "get_focus_mode" GodotLineEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_focus_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_focus_mode
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_focus_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_focus_mode #-}

instance Method "set_focus_mode" GodotLineEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_focus_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit__text_changed
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "_text_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit__text_changed #-}

instance Method "_text_changed" GodotLineEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit__text_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit__toggle_draw_caret
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "_toggle_draw_caret" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit__toggle_draw_caret #-}

instance Method "_toggle_draw_caret" GodotLineEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit__toggle_draw_caret (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit__editor_settings_changed
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "_editor_settings_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit__editor_settings_changed #-}

instance Method "_editor_settings_changed" GodotLineEdit (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit__editor_settings_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_align
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_align #-}

instance Method "set_align" GodotLineEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_align (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_align
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_align #-}

instance Method "get_align" GodotLineEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_align (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit__gui_input
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit__gui_input #-}

instance Method "_gui_input" GodotLineEdit
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_clear
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_clear #-}

instance Method "clear" GodotLineEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_select
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_select #-}

instance Method "select" GodotLineEdit (Int -> Int -> IO ()) where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_select (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_select_all
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "select_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_select_all #-}

instance Method "select_all" GodotLineEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_select_all (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_deselect
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "deselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_deselect #-}

instance Method "deselect" GodotLineEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_deselect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_text
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_text #-}

instance Method "set_text" GodotLineEdit (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_text
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_text #-}

instance Method "get_text" GodotLineEdit (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_placeholder
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_placeholder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_placeholder #-}

instance Method "set_placeholder" GodotLineEdit
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_placeholder (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_placeholder
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_placeholder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_placeholder #-}

instance Method "get_placeholder" GodotLineEdit (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_placeholder (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_placeholder_alpha
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_placeholder_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_placeholder_alpha #-}

instance Method "set_placeholder_alpha" GodotLineEdit
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_placeholder_alpha
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_placeholder_alpha
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_placeholder_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_placeholder_alpha #-}

instance Method "get_placeholder_alpha" GodotLineEdit (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_placeholder_alpha
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_cursor_position
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_cursor_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_cursor_position #-}

instance Method "set_cursor_position" GodotLineEdit (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_cursor_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_cursor_position
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_cursor_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_cursor_position #-}

instance Method "get_cursor_position" GodotLineEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_cursor_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_expand_to_text_length
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_expand_to_text_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_expand_to_text_length #-}

instance Method "set_expand_to_text_length" GodotLineEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_expand_to_text_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_expand_to_text_length
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_expand_to_text_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_expand_to_text_length #-}

instance Method "get_expand_to_text_length" GodotLineEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_expand_to_text_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_cursor_set_blink_enabled
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "cursor_set_blink_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_cursor_set_blink_enabled #-}

instance Method "cursor_set_blink_enabled" GodotLineEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_cursor_set_blink_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_cursor_get_blink_enabled
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "cursor_get_blink_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_cursor_get_blink_enabled #-}

instance Method "cursor_get_blink_enabled" GodotLineEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_cursor_get_blink_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_cursor_set_blink_speed
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "cursor_set_blink_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_cursor_set_blink_speed #-}

instance Method "cursor_set_blink_speed" GodotLineEdit
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_cursor_set_blink_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_cursor_get_blink_speed
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "cursor_get_blink_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_cursor_get_blink_speed #-}

instance Method "cursor_get_blink_speed" GodotLineEdit (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_cursor_get_blink_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_max_length
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_max_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_max_length #-}

instance Method "set_max_length" GodotLineEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_max_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_max_length
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_max_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_max_length #-}

instance Method "get_max_length" GodotLineEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_max_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_append_at_cursor
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "append_at_cursor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_append_at_cursor #-}

instance Method "append_at_cursor" GodotLineEdit
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_append_at_cursor (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_editable
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_editable #-}

instance Method "set_editable" GodotLineEdit (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_editable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_is_editable
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "is_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_is_editable #-}

instance Method "is_editable" GodotLineEdit (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_is_editable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_secret
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_secret" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_secret #-}

instance Method "set_secret" GodotLineEdit (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_secret (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_is_secret
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "is_secret" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_is_secret #-}

instance Method "is_secret" GodotLineEdit (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_is_secret (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_secret_character
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_secret_character" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_secret_character #-}

instance Method "set_secret_character" GodotLineEdit
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_secret_character
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_secret_character
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_secret_character" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_secret_character #-}

instance Method "get_secret_character" GodotLineEdit
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_secret_character
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_menu_option
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "menu_option" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_menu_option #-}

instance Method "menu_option" GodotLineEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_menu_option (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_get_menu
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "get_menu" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_get_menu #-}

instance Method "get_menu" GodotLineEdit (IO GodotPopupMenu) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_get_menu (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_context_menu_enabled
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_context_menu_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_context_menu_enabled #-}

instance Method "set_context_menu_enabled" GodotLineEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_context_menu_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_is_context_menu_enabled
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "is_context_menu_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_is_context_menu_enabled #-}

instance Method "is_context_menu_enabled" GodotLineEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_is_context_menu_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_set_clear_button_enabled
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "set_clear_button_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_set_clear_button_enabled #-}

instance Method "set_clear_button_enabled" GodotLineEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_set_clear_button_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineEdit_is_clear_button_enabled
  = unsafePerformIO $
      withCString "LineEdit" $
        \ clsNamePtr ->
          withCString "is_clear_button_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineEdit_is_clear_button_enabled #-}

instance Method "is_clear_button_enabled" GodotLineEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineEdit_is_clear_button_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVideoPlayer = GodotVideoPlayer GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotVideoPlayer where
        type BaseClass GodotVideoPlayer = GodotControl
        super = coerce
bindVideoPlayer_set_stream
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_stream #-}

instance Method "set_stream" GodotVideoPlayer
           (GodotVideoStream -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_stream (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_stream
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_stream #-}

instance Method "get_stream" GodotVideoPlayer (IO GodotVideoStream)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_stream (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_play
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_play #-}

instance Method "play" GodotVideoPlayer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_play (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_stop
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_stop #-}

instance Method "stop" GodotVideoPlayer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_stop (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_is_playing
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_is_playing #-}

instance Method "is_playing" GodotVideoPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_is_playing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_paused
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_paused #-}

instance Method "set_paused" GodotVideoPlayer (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_paused (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_is_paused
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "is_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_is_paused #-}

instance Method "is_paused" GodotVideoPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_is_paused (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_volume
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_volume" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_volume #-}

instance Method "set_volume" GodotVideoPlayer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_volume (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_volume
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_volume" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_volume #-}

instance Method "get_volume" GodotVideoPlayer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_volume (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_volume_db
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_volume_db #-}

instance Method "set_volume_db" GodotVideoPlayer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_volume_db (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_volume_db
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_volume_db #-}

instance Method "get_volume_db" GodotVideoPlayer (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_volume_db (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_audio_track
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_audio_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_audio_track #-}

instance Method "set_audio_track" GodotVideoPlayer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_audio_track (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_audio_track
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_audio_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_audio_track #-}

instance Method "get_audio_track" GodotVideoPlayer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_audio_track (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_stream_name
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_stream_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_stream_name #-}

instance Method "get_stream_name" GodotVideoPlayer (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_stream_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_stream_position
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_stream_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_stream_position #-}

instance Method "set_stream_position" GodotVideoPlayer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_stream_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_stream_position
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_stream_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_stream_position #-}

instance Method "get_stream_position" GodotVideoPlayer (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_stream_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_autoplay
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_autoplay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_autoplay #-}

instance Method "set_autoplay" GodotVideoPlayer (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_autoplay (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_has_autoplay
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "has_autoplay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_has_autoplay #-}

instance Method "has_autoplay" GodotVideoPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_has_autoplay (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_expand
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_expand #-}

instance Method "set_expand" GodotVideoPlayer (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_expand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_has_expand
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "has_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_has_expand #-}

instance Method "has_expand" GodotVideoPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_has_expand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_buffering_msec
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_buffering_msec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_buffering_msec #-}

instance Method "set_buffering_msec" GodotVideoPlayer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_buffering_msec
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_buffering_msec
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_buffering_msec" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_buffering_msec #-}

instance Method "get_buffering_msec" GodotVideoPlayer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_buffering_msec
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_set_bus
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "set_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_set_bus #-}

instance Method "set_bus" GodotVideoPlayer (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_set_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_bus
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_bus #-}

instance Method "get_bus" GodotVideoPlayer (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoPlayer_get_video_texture
  = unsafePerformIO $
      withCString "VideoPlayer" $
        \ clsNamePtr ->
          withCString "get_video_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoPlayer_get_video_texture #-}

instance Method "get_video_texture" GodotVideoPlayer
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoPlayer_get_video_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVideoStream = GodotVideoStream GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotVideoStream where
        type BaseClass GodotVideoStream = GodotResource
        super = coerce

newtype GodotWindowDialog = GodotWindowDialog GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotWindowDialog where
        type BaseClass GodotWindowDialog = GodotPopup
        super = coerce
bindWindowDialog__gui_input
  = unsafePerformIO $
      withCString "WindowDialog" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWindowDialog__gui_input #-}

instance Method "_gui_input" GodotWindowDialog
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWindowDialog__gui_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWindowDialog_set_title
  = unsafePerformIO $
      withCString "WindowDialog" $
        \ clsNamePtr ->
          withCString "set_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWindowDialog_set_title #-}

instance Method "set_title" GodotWindowDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWindowDialog_set_title (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWindowDialog_get_title
  = unsafePerformIO $
      withCString "WindowDialog" $
        \ clsNamePtr ->
          withCString "get_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWindowDialog_get_title #-}

instance Method "get_title" GodotWindowDialog (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWindowDialog_get_title (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWindowDialog_set_resizable
  = unsafePerformIO $
      withCString "WindowDialog" $
        \ clsNamePtr ->
          withCString "set_resizable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWindowDialog_set_resizable #-}

instance Method "set_resizable" GodotWindowDialog (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWindowDialog_set_resizable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWindowDialog_get_resizable
  = unsafePerformIO $
      withCString "WindowDialog" $
        \ clsNamePtr ->
          withCString "get_resizable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWindowDialog_get_resizable #-}

instance Method "get_resizable" GodotWindowDialog (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWindowDialog_get_resizable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWindowDialog__closed
  = unsafePerformIO $
      withCString "WindowDialog" $
        \ clsNamePtr ->
          withCString "_closed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWindowDialog__closed #-}

instance Method "_closed" GodotWindowDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWindowDialog__closed (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWindowDialog_get_close_button
  = unsafePerformIO $
      withCString "WindowDialog" $
        \ clsNamePtr ->
          withCString "get_close_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWindowDialog_get_close_button #-}

instance Method "get_close_button" GodotWindowDialog
           (IO GodotTextureButton)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWindowDialog_get_close_button
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAcceptDialog = GodotAcceptDialog GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotAcceptDialog where
        type BaseClass GodotAcceptDialog = GodotWindowDialog
        super = coerce
bindAcceptDialog__ok
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "_ok" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog__ok #-}

instance Method "_ok" GodotAcceptDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog__ok (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_get_ok
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "get_ok" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_get_ok #-}

instance Method "get_ok" GodotAcceptDialog (IO GodotButton) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_get_ok (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_get_label
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "get_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_get_label #-}

instance Method "get_label" GodotAcceptDialog (IO GodotLabel) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_get_label (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_set_hide_on_ok
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "set_hide_on_ok" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_set_hide_on_ok #-}

instance Method "set_hide_on_ok" GodotAcceptDialog (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_set_hide_on_ok (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_get_hide_on_ok
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "get_hide_on_ok" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_get_hide_on_ok #-}

instance Method "get_hide_on_ok" GodotAcceptDialog (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_get_hide_on_ok (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_add_button
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "add_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_add_button #-}

instance Method "add_button" GodotAcceptDialog
           (GodotString -> Bool -> GodotString -> IO GodotButton)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_add_button (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_add_cancel
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "add_cancel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_add_cancel #-}

instance Method "add_cancel" GodotAcceptDialog
           (GodotString -> IO GodotButton)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_add_cancel (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog__builtin_text_entered
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "_builtin_text_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog__builtin_text_entered #-}

instance Method "_builtin_text_entered" GodotAcceptDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog__builtin_text_entered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_register_text_enter
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "register_text_enter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_register_text_enter #-}

instance Method "register_text_enter" GodotAcceptDialog
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_register_text_enter
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog__custom_action
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "_custom_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog__custom_action #-}

instance Method "_custom_action" GodotAcceptDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog__custom_action (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_set_text
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_set_text #-}

instance Method "set_text" GodotAcceptDialog (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_set_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAcceptDialog_get_text
  = unsafePerformIO $
      withCString "AcceptDialog" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAcceptDialog_get_text #-}

instance Method "get_text" GodotAcceptDialog (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAcceptDialog_get_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotConfirmationDialog = GodotConfirmationDialog GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotConfirmationDialog where
        type BaseClass GodotConfirmationDialog = GodotAcceptDialog
        super = coerce
bindConfirmationDialog_get_cancel
  = unsafePerformIO $
      withCString "ConfirmationDialog" $
        \ clsNamePtr ->
          withCString "get_cancel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConfirmationDialog_get_cancel #-}

instance Method "get_cancel" GodotConfirmationDialog
           (IO GodotButton)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConfirmationDialog_get_cancel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotFileDialog = GodotFileDialog GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotFileDialog where
        type BaseClass GodotFileDialog = GodotConfirmationDialog
        super = coerce
bindFileDialog__unhandled_input
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__unhandled_input #-}

instance Method "_unhandled_input" GodotFileDialog
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__unhandled_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__tree_multi_selected
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_tree_multi_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__tree_multi_selected #-}

instance Method "_tree_multi_selected" GodotFileDialog
           (GodotObject -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__tree_multi_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__tree_selected
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_tree_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__tree_selected #-}

instance Method "_tree_selected" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__tree_selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__tree_item_activated
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_tree_item_activated" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__tree_item_activated #-}

instance Method "_tree_item_activated" GodotFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__tree_item_activated
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__dir_entered
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_dir_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__dir_entered #-}

instance Method "_dir_entered" GodotFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__dir_entered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__file_entered
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_file_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__file_entered #-}

instance Method "_file_entered" GodotFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__file_entered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__action_pressed
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_action_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__action_pressed #-}

instance Method "_action_pressed" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__action_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__cancel_pressed
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_cancel_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__cancel_pressed #-}

instance Method "_cancel_pressed" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__cancel_pressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__filter_selected
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_filter_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__filter_selected #-}

instance Method "_filter_selected" GodotFileDialog (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__filter_selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__save_confirm_pressed
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_save_confirm_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__save_confirm_pressed #-}

instance Method "_save_confirm_pressed" GodotFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__save_confirm_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_clear_filters
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "clear_filters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_clear_filters #-}

instance Method "clear_filters" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_clear_filters (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_add_filter
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "add_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_add_filter #-}

instance Method "add_filter" GodotFileDialog (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_add_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_filters
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_filters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_filters #-}

instance Method "set_filters" GodotFileDialog
           (GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_filters (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_filters
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_filters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_filters #-}

instance Method "get_filters" GodotFileDialog
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_filters (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_current_dir
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_current_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_current_dir #-}

instance Method "get_current_dir" GodotFileDialog (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_current_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_current_file
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_current_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_current_file #-}

instance Method "get_current_file" GodotFileDialog (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_current_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_current_path
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_current_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_current_path #-}

instance Method "get_current_path" GodotFileDialog (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_current_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_current_dir
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_current_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_current_dir #-}

instance Method "set_current_dir" GodotFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_current_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_current_file
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_current_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_current_file #-}

instance Method "set_current_file" GodotFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_current_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_current_path
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_current_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_current_path #-}

instance Method "set_current_path" GodotFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_current_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_mode_overrides_title
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_mode_overrides_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_mode_overrides_title #-}

instance Method "set_mode_overrides_title" GodotFileDialog
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_mode_overrides_title
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_is_mode_overriding_title
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "is_mode_overriding_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_is_mode_overriding_title #-}

instance Method "is_mode_overriding_title" GodotFileDialog
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_is_mode_overriding_title
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_mode
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_mode #-}

instance Method "set_mode" GodotFileDialog (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_mode
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_mode #-}

instance Method "get_mode" GodotFileDialog (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_vbox
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_vbox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_vbox #-}

instance Method "get_vbox" GodotFileDialog (IO GodotVBoxContainer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_vbox (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_line_edit
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_line_edit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_line_edit #-}

instance Method "get_line_edit" GodotFileDialog (IO GodotLineEdit)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_line_edit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_access
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_access" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_access #-}

instance Method "set_access" GodotFileDialog (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_access (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_get_access
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "get_access" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_get_access #-}

instance Method "get_access" GodotFileDialog (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_get_access (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_set_show_hidden_files
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "set_show_hidden_files" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_set_show_hidden_files #-}

instance Method "set_show_hidden_files" GodotFileDialog
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_set_show_hidden_files
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_is_showing_hidden_files
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "is_showing_hidden_files" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_is_showing_hidden_files #-}

instance Method "is_showing_hidden_files" GodotFileDialog (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_is_showing_hidden_files
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__select_drive
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_select_drive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__select_drive #-}

instance Method "_select_drive" GodotFileDialog (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__select_drive (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__make_dir
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_make_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__make_dir #-}

instance Method "_make_dir" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__make_dir (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__make_dir_confirm
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_make_dir_confirm" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__make_dir_confirm #-}

instance Method "_make_dir_confirm" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__make_dir_confirm
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__update_file_list
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_update_file_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__update_file_list #-}

instance Method "_update_file_list" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__update_file_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__update_dir
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_update_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__update_dir #-}

instance Method "_update_dir" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__update_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog__go_up
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "_go_up" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog__go_up #-}

instance Method "_go_up" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog__go_up (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_deselect_items
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "deselect_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_deselect_items #-}

instance Method "deselect_items" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_deselect_items (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFileDialog_invalidate
  = unsafePerformIO $
      withCString "FileDialog" $
        \ clsNamePtr ->
          withCString "invalidate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFileDialog_invalidate #-}

instance Method "invalidate" GodotFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFileDialog_invalidate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPopupMenu = GodotPopupMenu GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotPopupMenu where
        type BaseClass GodotPopupMenu = GodotPopup
        super = coerce
bindPopupMenu__gui_input
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu__gui_input #-}

instance Method "_gui_input" GodotPopupMenu
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_icon_item
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_icon_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_icon_item #-}

instance Method "add_icon_item" GodotPopupMenu
           (GodotTexture -> GodotString -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_icon_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_item
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_item #-}

instance Method "add_item" GodotPopupMenu
           (GodotString -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_item (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_icon_check_item
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_icon_check_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_icon_check_item #-}

instance Method "add_icon_check_item" GodotPopupMenu
           (GodotTexture -> GodotString -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_icon_check_item
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_check_item
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_check_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_check_item #-}

instance Method "add_check_item" GodotPopupMenu
           (GodotString -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_check_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_radio_check_item
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_radio_check_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_radio_check_item #-}

instance Method "add_radio_check_item" GodotPopupMenu
           (GodotString -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_radio_check_item
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_submenu_item
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_submenu_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_submenu_item #-}

instance Method "add_submenu_item" GodotPopupMenu
           (GodotString -> GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_submenu_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_icon_shortcut
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_icon_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_icon_shortcut #-}

instance Method "add_icon_shortcut" GodotPopupMenu
           (GodotTexture -> GodotShortCut -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_icon_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_shortcut
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_shortcut #-}

instance Method "add_shortcut" GodotPopupMenu
           (GodotShortCut -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_icon_check_shortcut
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_icon_check_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_icon_check_shortcut #-}

instance Method "add_icon_check_shortcut" GodotPopupMenu
           (GodotTexture -> GodotShortCut -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_icon_check_shortcut
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_check_shortcut
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_check_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_check_shortcut #-}

instance Method "add_check_shortcut" GodotPopupMenu
           (GodotShortCut -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_check_shortcut
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_radio_check_shortcut
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_radio_check_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_radio_check_shortcut #-}

instance Method "add_radio_check_shortcut" GodotPopupMenu
           (GodotShortCut -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_radio_check_shortcut
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_text
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_text #-}

instance Method "set_item_text" GodotPopupMenu
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_icon
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_icon #-}

instance Method "set_item_icon" GodotPopupMenu
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_checked
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_checked #-}

instance Method "set_item_checked" GodotPopupMenu
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_checked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_id
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_id #-}

instance Method "set_item_id" GodotPopupMenu (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_accelerator
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_accelerator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_accelerator #-}

instance Method "set_item_accelerator" GodotPopupMenu
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_accelerator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_metadata
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_metadata #-}

instance Method "set_item_metadata" GodotPopupMenu
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_metadata (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_disabled
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_disabled #-}

instance Method "set_item_disabled" GodotPopupMenu
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_submenu
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_submenu" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_submenu #-}

instance Method "set_item_submenu" GodotPopupMenu
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_submenu (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_as_separator
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_as_separator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_as_separator #-}

instance Method "set_item_as_separator" GodotPopupMenu
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_as_separator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_as_checkable
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_as_checkable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_as_checkable #-}

instance Method "set_item_as_checkable" GodotPopupMenu
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_as_checkable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_as_radio_checkable
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_as_radio_checkable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_as_radio_checkable #-}

instance Method "set_item_as_radio_checkable" GodotPopupMenu
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_as_radio_checkable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_tooltip
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_tooltip #-}

instance Method "set_item_tooltip" GodotPopupMenu
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_tooltip (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_shortcut
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_shortcut #-}

instance Method "set_item_shortcut" GodotPopupMenu
           (Int -> GodotShortCut -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_multistate
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_multistate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_multistate #-}

instance Method "set_item_multistate" GodotPopupMenu
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_multistate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_item_shortcut_disabled
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_item_shortcut_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_item_shortcut_disabled #-}

instance Method "set_item_shortcut_disabled" GodotPopupMenu
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_item_shortcut_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_toggle_item_checked
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "toggle_item_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_toggle_item_checked #-}

instance Method "toggle_item_checked" GodotPopupMenu (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_toggle_item_checked
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_toggle_item_multistate
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "toggle_item_multistate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_toggle_item_multistate #-}

instance Method "toggle_item_multistate" GodotPopupMenu
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_toggle_item_multistate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_text
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_text #-}

instance Method "get_item_text" GodotPopupMenu
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_icon
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_icon #-}

instance Method "get_item_icon" GodotPopupMenu
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_item_checked
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_item_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_item_checked #-}

instance Method "is_item_checked" GodotPopupMenu (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_item_checked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_id
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_id #-}

instance Method "get_item_id" GodotPopupMenu (Int -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_index
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_index #-}

instance Method "get_item_index" GodotPopupMenu (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_index (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_accelerator
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_accelerator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_accelerator #-}

instance Method "get_item_accelerator" GodotPopupMenu
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_accelerator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_metadata
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_metadata #-}

instance Method "get_item_metadata" GodotPopupMenu
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_metadata (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_item_disabled
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_item_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_item_disabled #-}

instance Method "is_item_disabled" GodotPopupMenu (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_item_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_submenu
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_submenu" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_submenu #-}

instance Method "get_item_submenu" GodotPopupMenu
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_submenu (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_item_separator
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_item_separator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_item_separator #-}

instance Method "is_item_separator" GodotPopupMenu (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_item_separator (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_item_checkable
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_item_checkable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_item_checkable #-}

instance Method "is_item_checkable" GodotPopupMenu (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_item_checkable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_item_radio_checkable
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_item_radio_checkable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_item_radio_checkable #-}

instance Method "is_item_radio_checkable" GodotPopupMenu
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_item_radio_checkable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_item_shortcut_disabled
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_item_shortcut_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_item_shortcut_disabled #-}

instance Method "is_item_shortcut_disabled" GodotPopupMenu
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_item_shortcut_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_tooltip
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_tooltip #-}

instance Method "get_item_tooltip" GodotPopupMenu
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_tooltip (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_shortcut
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_shortcut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_shortcut #-}

instance Method "get_item_shortcut" GodotPopupMenu
           (Int -> IO GodotShortCut)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_shortcut (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_item_count
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_item_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_item_count #-}

instance Method "get_item_count" GodotPopupMenu (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_item_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_remove_item
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "remove_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_remove_item #-}

instance Method "remove_item" GodotPopupMenu (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_remove_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_add_separator
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "add_separator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_add_separator #-}

instance Method "add_separator" GodotPopupMenu
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_add_separator (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_clear
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_clear #-}

instance Method "clear" GodotPopupMenu (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu__set_items
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "_set_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu__set_items #-}

instance Method "_set_items" GodotPopupMenu (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu__set_items (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu__get_items
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "_get_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu__get_items #-}

instance Method "_get_items" GodotPopupMenu (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu__get_items (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_hide_on_item_selection
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_hide_on_item_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_hide_on_item_selection #-}

instance Method "set_hide_on_item_selection" GodotPopupMenu
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_hide_on_item_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_hide_on_item_selection
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_hide_on_item_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_hide_on_item_selection #-}

instance Method "is_hide_on_item_selection" GodotPopupMenu
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_hide_on_item_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_hide_on_checkable_item_selection
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_hide_on_checkable_item_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_hide_on_checkable_item_selection #-}

instance Method "set_hide_on_checkable_item_selection"
           GodotPopupMenu
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPopupMenu_set_hide_on_checkable_item_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_hide_on_checkable_item_selection
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_hide_on_checkable_item_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_hide_on_checkable_item_selection #-}

instance Method "is_hide_on_checkable_item_selection"
           GodotPopupMenu
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPopupMenu_is_hide_on_checkable_item_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_hide_on_state_item_selection
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_hide_on_state_item_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_hide_on_state_item_selection #-}

instance Method "set_hide_on_state_item_selection" GodotPopupMenu
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPopupMenu_set_hide_on_state_item_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_hide_on_state_item_selection
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_hide_on_state_item_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_hide_on_state_item_selection #-}

instance Method "is_hide_on_state_item_selection" GodotPopupMenu
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPopupMenu_is_hide_on_state_item_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_submenu_popup_delay
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_submenu_popup_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_submenu_popup_delay #-}

instance Method "set_submenu_popup_delay" GodotPopupMenu
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_submenu_popup_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_get_submenu_popup_delay
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "get_submenu_popup_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_get_submenu_popup_delay #-}

instance Method "get_submenu_popup_delay" GodotPopupMenu (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_get_submenu_popup_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_set_hide_on_window_lose_focus
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "set_hide_on_window_lose_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_set_hide_on_window_lose_focus #-}

instance Method "set_hide_on_window_lose_focus" GodotPopupMenu
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_set_hide_on_window_lose_focus
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu_is_hide_on_window_lose_focus
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "is_hide_on_window_lose_focus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu_is_hide_on_window_lose_focus #-}

instance Method "is_hide_on_window_lose_focus" GodotPopupMenu
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu_is_hide_on_window_lose_focus
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPopupMenu__submenu_timeout
  = unsafePerformIO $
      withCString "PopupMenu" $
        \ clsNamePtr ->
          withCString "_submenu_timeout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPopupMenu__submenu_timeout #-}

instance Method "_submenu_timeout" GodotPopupMenu (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPopupMenu__submenu_timeout (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTree = GodotTree GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotTree where
        type BaseClass GodotTree = GodotControl
        super = coerce
bindTree__range_click_timeout
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "_range_click_timeout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree__range_click_timeout #-}

instance Method "_range_click_timeout" GodotTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree__range_click_timeout (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree__gui_input
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree__gui_input #-}

instance Method "_gui_input" GodotTree (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree__gui_input (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree__popup_select
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "_popup_select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree__popup_select #-}

instance Method "_popup_select" GodotTree (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree__popup_select (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree__text_editor_enter
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "_text_editor_enter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree__text_editor_enter #-}

instance Method "_text_editor_enter" GodotTree
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree__text_editor_enter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree__text_editor_modal_close
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "_text_editor_modal_close" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree__text_editor_modal_close #-}

instance Method "_text_editor_modal_close" GodotTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree__text_editor_modal_close
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree__value_editor_changed
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "_value_editor_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree__value_editor_changed #-}

instance Method "_value_editor_changed" GodotTree (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree__value_editor_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree__scroll_moved
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "_scroll_moved" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree__scroll_moved #-}

instance Method "_scroll_moved" GodotTree (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree__scroll_moved (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_clear
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_clear #-}

instance Method "clear" GodotTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_clear (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_create_item
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "create_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_create_item #-}

instance Method "create_item" GodotTree
           (GodotObject -> Int -> IO GodotTreeItem)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_create_item (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_root
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_root #-}

instance Method "get_root" GodotTree (IO GodotTreeItem) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_root (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_column_min_width
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_column_min_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_column_min_width #-}

instance Method "set_column_min_width" GodotTree
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_column_min_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_column_expand
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_column_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_column_expand #-}

instance Method "set_column_expand" GodotTree
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_column_expand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_column_width
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_column_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_column_width #-}

instance Method "get_column_width" GodotTree (Int -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_column_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_hide_root
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_hide_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_hide_root #-}

instance Method "set_hide_root" GodotTree (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_hide_root (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_is_root_hidden
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "is_root_hidden" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_is_root_hidden #-}

instance Method "is_root_hidden" GodotTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_is_root_hidden (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_next_selected
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_next_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_next_selected #-}

instance Method "get_next_selected" GodotTree
           (GodotObject -> IO GodotTreeItem)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_next_selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_selected
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_selected #-}

instance Method "get_selected" GodotTree (IO GodotTreeItem) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_selected (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_selected_column
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_selected_column" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_selected_column #-}

instance Method "get_selected_column" GodotTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_selected_column (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_pressed_button
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_pressed_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_pressed_button #-}

instance Method "get_pressed_button" GodotTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_pressed_button (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_select_mode
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_select_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_select_mode #-}

instance Method "set_select_mode" GodotTree (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_select_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_select_mode
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_select_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_select_mode #-}

instance Method "get_select_mode" GodotTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_select_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_columns
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_columns" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_columns #-}

instance Method "set_columns" GodotTree (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_columns (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_columns
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_columns" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_columns #-}

instance Method "get_columns" GodotTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_columns (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_edited
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_edited" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_edited #-}

instance Method "get_edited" GodotTree (IO GodotTreeItem) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_edited (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_edited_column
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_edited_column" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_edited_column #-}

instance Method "get_edited_column" GodotTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_edited_column (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_custom_popup_rect
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_custom_popup_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_custom_popup_rect #-}

instance Method "get_custom_popup_rect" GodotTree (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_custom_popup_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_item_area_rect
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_item_area_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_item_area_rect #-}

instance Method "get_item_area_rect" GodotTree
           (GodotObject -> Int -> IO GodotRect2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_item_area_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_item_at_position
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_item_at_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_item_at_position #-}

instance Method "get_item_at_position" GodotTree
           (GodotVector2 -> IO GodotTreeItem)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_item_at_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_column_at_position
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_column_at_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_column_at_position #-}

instance Method "get_column_at_position" GodotTree
           (GodotVector2 -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_column_at_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_drop_section_at_position
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_drop_section_at_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_drop_section_at_position #-}

instance Method "get_drop_section_at_position" GodotTree
           (GodotVector2 -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_drop_section_at_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_ensure_cursor_is_visible
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "ensure_cursor_is_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_ensure_cursor_is_visible #-}

instance Method "ensure_cursor_is_visible" GodotTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_ensure_cursor_is_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_column_titles_visible
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_column_titles_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_column_titles_visible #-}

instance Method "set_column_titles_visible" GodotTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_column_titles_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_are_column_titles_visible
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "are_column_titles_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_are_column_titles_visible #-}

instance Method "are_column_titles_visible" GodotTree (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_are_column_titles_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_column_title
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_column_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_column_title #-}

instance Method "set_column_title" GodotTree
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_column_title (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_column_title
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_column_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_column_title #-}

instance Method "get_column_title" GodotTree
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_column_title (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_scroll
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_scroll #-}

instance Method "get_scroll" GodotTree (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_scroll (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_hide_folding
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_hide_folding" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_hide_folding #-}

instance Method "set_hide_folding" GodotTree (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_hide_folding (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_is_folding_hidden
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "is_folding_hidden" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_is_folding_hidden #-}

instance Method "is_folding_hidden" GodotTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_is_folding_hidden (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_drop_mode_flags
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_drop_mode_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_drop_mode_flags #-}

instance Method "set_drop_mode_flags" GodotTree (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_drop_mode_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_drop_mode_flags
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_drop_mode_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_drop_mode_flags #-}

instance Method "get_drop_mode_flags" GodotTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_drop_mode_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_allow_rmb_select
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_allow_rmb_select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_allow_rmb_select #-}

instance Method "set_allow_rmb_select" GodotTree (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_allow_rmb_select (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_allow_rmb_select
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_allow_rmb_select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_allow_rmb_select #-}

instance Method "get_allow_rmb_select" GodotTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_allow_rmb_select (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_set_allow_reselect
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "set_allow_reselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_set_allow_reselect #-}

instance Method "set_allow_reselect" GodotTree (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_set_allow_reselect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTree_get_allow_reselect
  = unsafePerformIO $
      withCString "Tree" $
        \ clsNamePtr ->
          withCString "get_allow_reselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTree_get_allow_reselect #-}

instance Method "get_allow_reselect" GodotTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTree_get_allow_reselect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTreeItem = GodotTreeItem GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotTreeItem where
        type BaseClass GodotTreeItem = GodotObject
        super = coerce
bindTreeItem_set_cell_mode
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_cell_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_cell_mode #-}

instance Method "set_cell_mode" GodotTreeItem (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_cell_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_cell_mode
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_cell_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_cell_mode #-}

instance Method "get_cell_mode" GodotTreeItem (Int -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_cell_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_checked
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_checked #-}

instance Method "set_checked" GodotTreeItem (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_checked (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_checked
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_checked #-}

instance Method "is_checked" GodotTreeItem (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_checked (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_text
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_text #-}

instance Method "set_text" GodotTreeItem
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_text
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_text #-}

instance Method "get_text" GodotTreeItem (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_icon
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_icon #-}

instance Method "set_icon" GodotTreeItem
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_icon (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_icon
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_icon #-}

instance Method "get_icon" GodotTreeItem (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_icon (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_icon_region
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_icon_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_icon_region #-}

instance Method "set_icon_region" GodotTreeItem
           (Int -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_icon_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_icon_region
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_icon_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_icon_region #-}

instance Method "get_icon_region" GodotTreeItem
           (Int -> IO GodotRect2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_icon_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_icon_max_width
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_icon_max_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_icon_max_width #-}

instance Method "set_icon_max_width" GodotTreeItem
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_icon_max_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_icon_max_width
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_icon_max_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_icon_max_width #-}

instance Method "get_icon_max_width" GodotTreeItem (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_icon_max_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_range
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_range #-}

instance Method "set_range" GodotTreeItem (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_range (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_range
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_range #-}

instance Method "get_range" GodotTreeItem (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_range (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_range_config
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_range_config" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_range_config #-}

instance Method "set_range_config" GodotTreeItem
           (Int -> Float -> Float -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_range_config (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_range_config
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_range_config" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_range_config #-}

instance Method "get_range_config" GodotTreeItem
           (Int -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_range_config (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_metadata
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_metadata #-}

instance Method "set_metadata" GodotTreeItem
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_metadata (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_metadata
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_metadata #-}

instance Method "get_metadata" GodotTreeItem
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_metadata (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_custom_draw
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_custom_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_custom_draw #-}

instance Method "set_custom_draw" GodotTreeItem
           (Int -> GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_custom_draw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_collapsed
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_collapsed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_collapsed #-}

instance Method "set_collapsed" GodotTreeItem (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_collapsed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_collapsed
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_collapsed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_collapsed #-}

instance Method "is_collapsed" GodotTreeItem (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_collapsed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_custom_minimum_height
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_custom_minimum_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_custom_minimum_height #-}

instance Method "set_custom_minimum_height" GodotTreeItem
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_custom_minimum_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_custom_minimum_height
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_custom_minimum_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_custom_minimum_height #-}

instance Method "get_custom_minimum_height" GodotTreeItem (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_custom_minimum_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_next
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_next #-}

instance Method "get_next" GodotTreeItem (IO GodotTreeItem) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_next (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_prev
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_prev" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_prev #-}

instance Method "get_prev" GodotTreeItem (IO GodotTreeItem) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_prev (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_parent
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_parent #-}

instance Method "get_parent" GodotTreeItem (IO GodotTreeItem) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_parent (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_children
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_children" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_children #-}

instance Method "get_children" GodotTreeItem (IO GodotTreeItem)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_children (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_next_visible
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_next_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_next_visible #-}

instance Method "get_next_visible" GodotTreeItem (IO GodotTreeItem)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_next_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_prev_visible
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_prev_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_prev_visible #-}

instance Method "get_prev_visible" GodotTreeItem (IO GodotTreeItem)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_prev_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_remove_child
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "remove_child" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_remove_child #-}

instance Method "remove_child" GodotTreeItem (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_remove_child (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_selectable
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_selectable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_selectable #-}

instance Method "set_selectable" GodotTreeItem
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_selectable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_selectable
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_selectable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_selectable #-}

instance Method "is_selectable" GodotTreeItem (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_selectable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_selected
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_selected #-}

instance Method "is_selected" GodotTreeItem (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_selected (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_select
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_select #-}

instance Method "select" GodotTreeItem (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_select (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_deselect
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "deselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_deselect #-}

instance Method "deselect" GodotTreeItem (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_deselect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_editable
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_editable #-}

instance Method "set_editable" GodotTreeItem (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_editable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_editable
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_editable #-}

instance Method "is_editable" GodotTreeItem (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_editable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_custom_color
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_custom_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_custom_color #-}

instance Method "set_custom_color" GodotTreeItem
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_custom_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_clear_custom_color
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "clear_custom_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_clear_custom_color #-}

instance Method "clear_custom_color" GodotTreeItem (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_clear_custom_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_custom_bg_color
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_custom_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_custom_bg_color #-}

instance Method "set_custom_bg_color" GodotTreeItem
           (Int -> GodotColor -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_custom_bg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_clear_custom_bg_color
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "clear_custom_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_clear_custom_bg_color #-}

instance Method "clear_custom_bg_color" GodotTreeItem
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_clear_custom_bg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_custom_bg_color
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_custom_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_custom_bg_color #-}

instance Method "get_custom_bg_color" GodotTreeItem
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_custom_bg_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_custom_as_button
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_custom_as_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_custom_as_button #-}

instance Method "set_custom_as_button" GodotTreeItem
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_custom_as_button
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_custom_set_as_button
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_custom_set_as_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_custom_set_as_button #-}

instance Method "is_custom_set_as_button" GodotTreeItem
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_custom_set_as_button
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_add_button
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "add_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_add_button #-}

instance Method "add_button" GodotTreeItem
           (Int -> GodotTexture -> Int -> Bool -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_add_button (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_button_count
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_button_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_button_count #-}

instance Method "get_button_count" GodotTreeItem (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_button_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_button
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_button #-}

instance Method "get_button" GodotTreeItem
           (Int -> Int -> IO GodotTexture)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_button (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_button
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_button #-}

instance Method "set_button" GodotTreeItem
           (Int -> Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_button (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_erase_button
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "erase_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_erase_button #-}

instance Method "erase_button" GodotTreeItem (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_erase_button (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_button_disabled
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_button_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_button_disabled #-}

instance Method "is_button_disabled" GodotTreeItem
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_button_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_expand_right
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_expand_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_expand_right #-}

instance Method "set_expand_right" GodotTreeItem
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_expand_right (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_expand_right
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_expand_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_expand_right #-}

instance Method "get_expand_right" GodotTreeItem (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_expand_right (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_tooltip
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_tooltip #-}

instance Method "set_tooltip" GodotTreeItem
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_tooltip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_tooltip
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_tooltip #-}

instance Method "get_tooltip" GodotTreeItem (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_tooltip (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_text_align
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_text_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_text_align #-}

instance Method "set_text_align" GodotTreeItem
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_text_align (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_get_text_align
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "get_text_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_get_text_align #-}

instance Method "get_text_align" GodotTreeItem (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_get_text_align (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_move_to_top
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "move_to_top" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_move_to_top #-}

instance Method "move_to_top" GodotTreeItem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_move_to_top (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_move_to_bottom
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "move_to_bottom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_move_to_bottom #-}

instance Method "move_to_bottom" GodotTreeItem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_move_to_bottom (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_set_disable_folding
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "set_disable_folding" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_set_disable_folding #-}

instance Method "set_disable_folding" GodotTreeItem (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_set_disable_folding
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTreeItem_is_folding_disabled
  = unsafePerformIO $
      withCString "TreeItem" $
        \ clsNamePtr ->
          withCString "is_folding_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTreeItem_is_folding_disabled #-}

instance Method "is_folding_disabled" GodotTreeItem (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTreeItem_is_folding_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTextEdit = GodotTextEdit GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotTextEdit where
        type BaseClass GodotTextEdit = GodotControl
        super = coerce
bindTextEdit__gui_input
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__gui_input #-}

instance Method "_gui_input" GodotTextEdit
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit__scroll_moved
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_scroll_moved" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__scroll_moved #-}

instance Method "_scroll_moved" GodotTextEdit (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__scroll_moved (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit__cursor_changed_emit
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_cursor_changed_emit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__cursor_changed_emit #-}

instance Method "_cursor_changed_emit" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__cursor_changed_emit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit__text_changed_emit
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_text_changed_emit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__text_changed_emit #-}

instance Method "_text_changed_emit" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__text_changed_emit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit__push_current_op
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_push_current_op" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__push_current_op #-}

instance Method "_push_current_op" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__push_current_op (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit__click_selection_held
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_click_selection_held" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__click_selection_held #-}

instance Method "_click_selection_held" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__click_selection_held
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit__toggle_draw_caret
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_toggle_draw_caret" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__toggle_draw_caret #-}

instance Method "_toggle_draw_caret" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__toggle_draw_caret (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit__v_scroll_input
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "_v_scroll_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit__v_scroll_input #-}

instance Method "_v_scroll_input" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit__v_scroll_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_text
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_text #-}

instance Method "set_text" GodotTextEdit (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_insert_text_at_cursor
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "insert_text_at_cursor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_insert_text_at_cursor #-}

instance Method "insert_text_at_cursor" GodotTextEdit
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_insert_text_at_cursor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_line_count
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_line_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_line_count #-}

instance Method "get_line_count" GodotTextEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_line_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_text
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_text #-}

instance Method "get_text" GodotTextEdit (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_text (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_line #-}

instance Method "get_line" GodotTextEdit (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_line (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_set_column
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_set_column" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_set_column #-}

instance Method "cursor_set_column" GodotTextEdit
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_set_column (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_set_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_set_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_set_line #-}

instance Method "cursor_set_line" GodotTextEdit
           (Int -> Bool -> Bool -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_set_line (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_get_column
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_get_column" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_get_column #-}

instance Method "cursor_get_column" GodotTextEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_get_column (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_get_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_get_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_get_line #-}

instance Method "cursor_get_line" GodotTextEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_get_line (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_set_blink_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_set_blink_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_set_blink_enabled #-}

instance Method "cursor_set_blink_enabled" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_set_blink_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_get_blink_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_get_blink_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_get_blink_enabled #-}

instance Method "cursor_get_blink_enabled" GodotTextEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_get_blink_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_set_blink_speed
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_set_blink_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_set_blink_speed #-}

instance Method "cursor_set_blink_speed" GodotTextEdit
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_set_blink_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_get_blink_speed
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_get_blink_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_get_blink_speed #-}

instance Method "cursor_get_blink_speed" GodotTextEdit (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_get_blink_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_set_block_mode
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_set_block_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_set_block_mode #-}

instance Method "cursor_set_block_mode" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_set_block_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cursor_is_block_mode
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cursor_is_block_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cursor_is_block_mode #-}

instance Method "cursor_is_block_mode" GodotTextEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cursor_is_block_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_right_click_moves_caret
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_right_click_moves_caret" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_right_click_moves_caret #-}

instance Method "set_right_click_moves_caret" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_right_click_moves_caret
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_right_click_moving_caret
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_right_click_moving_caret" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_right_click_moving_caret #-}

instance Method "is_right_click_moving_caret" GodotTextEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_right_click_moving_caret
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_readonly
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_readonly" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_readonly #-}

instance Method "set_readonly" GodotTextEdit (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_readonly (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_readonly
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_readonly" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_readonly #-}

instance Method "is_readonly" GodotTextEdit (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_readonly (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_wrap_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_wrap_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_wrap_enabled #-}

instance Method "set_wrap_enabled" GodotTextEdit (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_wrap_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_wrap_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_wrap_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_wrap_enabled #-}

instance Method "is_wrap_enabled" GodotTextEdit (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_wrap_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_context_menu_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_context_menu_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_context_menu_enabled #-}

instance Method "set_context_menu_enabled" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_context_menu_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_context_menu_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_context_menu_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_context_menu_enabled #-}

instance Method "is_context_menu_enabled" GodotTextEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_context_menu_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_cut
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "cut" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_cut #-}

instance Method "cut" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_cut (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_copy
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "copy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_copy #-}

instance Method "copy" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_copy (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_paste
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "paste" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_paste #-}

instance Method "paste" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_paste (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_select
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_select #-}

instance Method "select" GodotTextEdit
           (Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_select (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_select_all
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "select_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_select_all #-}

instance Method "select_all" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_select_all (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_deselect
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "deselect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_deselect #-}

instance Method "deselect" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_deselect (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_selection_active
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_selection_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_selection_active #-}

instance Method "is_selection_active" GodotTextEdit (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_selection_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_selection_from_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_selection_from_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_selection_from_line #-}

instance Method "get_selection_from_line" GodotTextEdit (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_selection_from_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_selection_from_column
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_selection_from_column" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_selection_from_column #-}

instance Method "get_selection_from_column" GodotTextEdit (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_selection_from_column
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_selection_to_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_selection_to_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_selection_to_line #-}

instance Method "get_selection_to_line" GodotTextEdit (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_selection_to_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_selection_to_column
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_selection_to_column" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_selection_to_column #-}

instance Method "get_selection_to_column" GodotTextEdit (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_selection_to_column
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_selection_text
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_selection_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_selection_text #-}

instance Method "get_selection_text" GodotTextEdit (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_selection_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_word_under_cursor
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_word_under_cursor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_word_under_cursor #-}

instance Method "get_word_under_cursor" GodotTextEdit
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_word_under_cursor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_search
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "search" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_search #-}

instance Method "search" GodotTextEdit
           (GodotString -> Int -> Int -> Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_search (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_undo
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "undo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_undo #-}

instance Method "undo" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_undo (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_redo
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "redo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_redo #-}

instance Method "redo" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_redo (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_clear_undo_history
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "clear_undo_history" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_clear_undo_history #-}

instance Method "clear_undo_history" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_clear_undo_history (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_show_line_numbers
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_show_line_numbers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_show_line_numbers #-}

instance Method "set_show_line_numbers" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_show_line_numbers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_show_line_numbers_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_show_line_numbers_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_show_line_numbers_enabled #-}

instance Method "is_show_line_numbers_enabled" GodotTextEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_show_line_numbers_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_breakpoint_gutter_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_breakpoint_gutter_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_breakpoint_gutter_enabled #-}

instance Method "set_breakpoint_gutter_enabled" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_breakpoint_gutter_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_breakpoint_gutter_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_breakpoint_gutter_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_breakpoint_gutter_enabled #-}

instance Method "is_breakpoint_gutter_enabled" GodotTextEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_breakpoint_gutter_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_hiding_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_hiding_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_hiding_enabled #-}

instance Method "set_hiding_enabled" GodotTextEdit (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_hiding_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_hiding_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_hiding_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_hiding_enabled #-}

instance Method "is_hiding_enabled" GodotTextEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_hiding_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_line_as_hidden
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_line_as_hidden" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_line_as_hidden #-}

instance Method "set_line_as_hidden" GodotTextEdit
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_line_as_hidden (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_line_hidden
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_line_hidden" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_line_hidden #-}

instance Method "is_line_hidden" GodotTextEdit (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_line_hidden (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_fold_all_lines
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "fold_all_lines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_fold_all_lines #-}

instance Method "fold_all_lines" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_fold_all_lines (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_unhide_all_lines
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "unhide_all_lines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_unhide_all_lines #-}

instance Method "unhide_all_lines" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_unhide_all_lines (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_fold_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "fold_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_fold_line #-}

instance Method "fold_line" GodotTextEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_fold_line (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_unfold_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "unfold_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_unfold_line #-}

instance Method "unfold_line" GodotTextEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_unfold_line (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_toggle_fold_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "toggle_fold_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_toggle_fold_line #-}

instance Method "toggle_fold_line" GodotTextEdit (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_toggle_fold_line (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_can_fold
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "can_fold" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_can_fold #-}

instance Method "can_fold" GodotTextEdit (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_can_fold (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_folded
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_folded" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_folded #-}

instance Method "is_folded" GodotTextEdit (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_folded (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_highlight_all_occurrences
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_highlight_all_occurrences" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_highlight_all_occurrences #-}

instance Method "set_highlight_all_occurrences" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_highlight_all_occurrences
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_highlight_all_occurrences_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_highlight_all_occurrences_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_highlight_all_occurrences_enabled #-}

instance Method "is_highlight_all_occurrences_enabled"
           GodotTextEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTextEdit_is_highlight_all_occurrences_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_override_selected_font_color
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_override_selected_font_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_override_selected_font_color #-}

instance Method "set_override_selected_font_color" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTextEdit_set_override_selected_font_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_overriding_selected_font_color
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_overriding_selected_font_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_overriding_selected_font_color #-}

instance Method "is_overriding_selected_font_color" GodotTextEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTextEdit_is_overriding_selected_font_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_syntax_coloring
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_syntax_coloring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_syntax_coloring #-}

instance Method "set_syntax_coloring" GodotTextEdit (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_syntax_coloring
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_syntax_coloring_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_syntax_coloring_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_syntax_coloring_enabled #-}

instance Method "is_syntax_coloring_enabled" GodotTextEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_syntax_coloring_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_highlight_current_line
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_highlight_current_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_highlight_current_line #-}

instance Method "set_highlight_current_line" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_highlight_current_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_highlight_current_line_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_highlight_current_line_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_highlight_current_line_enabled #-}

instance Method "is_highlight_current_line_enabled" GodotTextEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTextEdit_is_highlight_current_line_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_smooth_scroll_enable
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_smooth_scroll_enable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_smooth_scroll_enable #-}

instance Method "set_smooth_scroll_enable" GodotTextEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_smooth_scroll_enable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_is_smooth_scroll_enabled
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "is_smooth_scroll_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_is_smooth_scroll_enabled #-}

instance Method "is_smooth_scroll_enabled" GodotTextEdit (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_is_smooth_scroll_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_set_v_scroll_speed
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "set_v_scroll_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_set_v_scroll_speed #-}

instance Method "set_v_scroll_speed" GodotTextEdit (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_set_v_scroll_speed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_v_scroll_speed
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_v_scroll_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_v_scroll_speed #-}

instance Method "get_v_scroll_speed" GodotTextEdit (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_v_scroll_speed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_add_keyword_color
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "add_keyword_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_add_keyword_color #-}

instance Method "add_keyword_color" GodotTextEdit
           (GodotString -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_add_keyword_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_has_keyword_color
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "has_keyword_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_has_keyword_color #-}

instance Method "has_keyword_color" GodotTextEdit
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_has_keyword_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_keyword_color
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_keyword_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_keyword_color #-}

instance Method "get_keyword_color" GodotTextEdit
           (GodotString -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_keyword_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_add_color_region
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "add_color_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_add_color_region #-}

instance Method "add_color_region" GodotTextEdit
           (GodotString -> GodotString -> GodotColor -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_add_color_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_clear_colors
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "clear_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_clear_colors #-}

instance Method "clear_colors" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_clear_colors (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_menu_option
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "menu_option" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_menu_option #-}

instance Method "menu_option" GodotTextEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_menu_option (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_menu
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_menu" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_menu #-}

instance Method "get_menu" GodotTextEdit (IO GodotPopupMenu) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_menu (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_get_breakpoints
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "get_breakpoints" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_get_breakpoints #-}

instance Method "get_breakpoints" GodotTextEdit (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_get_breakpoints (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextEdit_remove_breakpoints
  = unsafePerformIO $
      withCString "TextEdit" $
        \ clsNamePtr ->
          withCString "remove_breakpoints" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextEdit_remove_breakpoints #-}

instance Method "remove_breakpoints" GodotTextEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextEdit_remove_breakpoints (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotOptionButton = GodotOptionButton GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotOptionButton where
        type BaseClass GodotOptionButton = GodotButton
        super = coerce
bindOptionButton__selected
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton__selected #-}

instance Method "_selected" GodotOptionButton (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton__selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton__focused
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "_focused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton__focused #-}

instance Method "_focused" GodotOptionButton (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton__focused (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_add_item
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "add_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_add_item #-}

instance Method "add_item" GodotOptionButton
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_add_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_add_icon_item
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "add_icon_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_add_icon_item #-}

instance Method "add_icon_item" GodotOptionButton
           (GodotTexture -> GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_add_icon_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_set_item_text
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "set_item_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_set_item_text #-}

instance Method "set_item_text" GodotOptionButton
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_set_item_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_set_item_icon
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "set_item_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_set_item_icon #-}

instance Method "set_item_icon" GodotOptionButton
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_set_item_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_set_item_disabled
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "set_item_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_set_item_disabled #-}

instance Method "set_item_disabled" GodotOptionButton
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_set_item_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_set_item_id
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "set_item_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_set_item_id #-}

instance Method "set_item_id" GodotOptionButton
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_set_item_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_set_item_metadata
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "set_item_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_set_item_metadata #-}

instance Method "set_item_metadata" GodotOptionButton
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_set_item_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_item_text
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_item_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_item_text #-}

instance Method "get_item_text" GodotOptionButton
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_item_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_item_icon
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_item_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_item_icon #-}

instance Method "get_item_icon" GodotOptionButton
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_item_icon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_item_id
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_item_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_item_id #-}

instance Method "get_item_id" GodotOptionButton (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_item_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_item_metadata
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_item_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_item_metadata #-}

instance Method "get_item_metadata" GodotOptionButton
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_item_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_is_item_disabled
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "is_item_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_is_item_disabled #-}

instance Method "is_item_disabled" GodotOptionButton
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_is_item_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_item_count
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_item_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_item_count #-}

instance Method "get_item_count" GodotOptionButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_item_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_add_separator
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "add_separator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_add_separator #-}

instance Method "add_separator" GodotOptionButton (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_add_separator (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_clear
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_clear #-}

instance Method "clear" GodotOptionButton (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_select
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "select" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_select #-}

instance Method "select" GodotOptionButton (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_select (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_selected
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_selected #-}

instance Method "get_selected" GodotOptionButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_selected_id
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_selected_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_selected_id #-}

instance Method "get_selected_id" GodotOptionButton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_selected_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_selected_metadata
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_selected_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_selected_metadata #-}

instance Method "get_selected_metadata" GodotOptionButton
           (IO GodotVariant)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_selected_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_remove_item
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "remove_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_remove_item #-}

instance Method "remove_item" GodotOptionButton (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_remove_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton__select_int
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "_select_int" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton__select_int #-}

instance Method "_select_int" GodotOptionButton (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton__select_int (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton_get_popup
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "get_popup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton_get_popup #-}

instance Method "get_popup" GodotOptionButton (IO GodotPopupMenu)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton_get_popup (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton__set_items
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "_set_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton__set_items #-}

instance Method "_set_items" GodotOptionButton
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton__set_items (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOptionButton__get_items
  = unsafePerformIO $
      withCString "OptionButton" $
        \ clsNamePtr ->
          withCString "_get_items" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOptionButton__get_items #-}

instance Method "_get_items" GodotOptionButton (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOptionButton__get_items (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpinBox = GodotSpinBox GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotSpinBox where
        type BaseClass GodotSpinBox = GodotRange
        super = coerce
bindSpinBox__gui_input
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox__gui_input #-}

instance Method "_gui_input" GodotSpinBox
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox__text_entered
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "_text_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox__text_entered #-}

instance Method "_text_entered" GodotSpinBox (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox__text_entered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_set_align
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "set_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_set_align #-}

instance Method "set_align" GodotSpinBox (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_set_align (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_get_align
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "get_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_get_align #-}

instance Method "get_align" GodotSpinBox (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_get_align (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_set_suffix
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "set_suffix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_set_suffix #-}

instance Method "set_suffix" GodotSpinBox (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_set_suffix (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_get_suffix
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "get_suffix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_get_suffix #-}

instance Method "get_suffix" GodotSpinBox (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_get_suffix (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_set_prefix
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "set_prefix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_set_prefix #-}

instance Method "set_prefix" GodotSpinBox (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_set_prefix (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_get_prefix
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "get_prefix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_get_prefix #-}

instance Method "get_prefix" GodotSpinBox (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_get_prefix (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_set_editable
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "set_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_set_editable #-}

instance Method "set_editable" GodotSpinBox (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_set_editable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_is_editable
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "is_editable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_is_editable #-}

instance Method "is_editable" GodotSpinBox (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_is_editable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox__line_edit_focus_exit
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "_line_edit_focus_exit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox__line_edit_focus_exit #-}

instance Method "_line_edit_focus_exit" GodotSpinBox (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox__line_edit_focus_exit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox_get_line_edit
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "get_line_edit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox_get_line_edit #-}

instance Method "get_line_edit" GodotSpinBox (IO GodotLineEdit)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox_get_line_edit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox__line_edit_input
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "_line_edit_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox__line_edit_input #-}

instance Method "_line_edit_input" GodotSpinBox
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox__line_edit_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpinBox__range_click_timeout
  = unsafePerformIO $
      withCString "SpinBox" $
        \ clsNamePtr ->
          withCString "_range_click_timeout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpinBox__range_click_timeout #-}

instance Method "_range_click_timeout" GodotSpinBox (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpinBox__range_click_timeout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotReferenceRect = GodotReferenceRect GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotReferenceRect where
        type BaseClass GodotReferenceRect = GodotControl
        super = coerce
bindReferenceRect_get_border_color
  = unsafePerformIO $
      withCString "ReferenceRect" $
        \ clsNamePtr ->
          withCString "get_border_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReferenceRect_get_border_color #-}

instance Method "get_border_color" GodotReferenceRect
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReferenceRect_get_border_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReferenceRect_set_border_color
  = unsafePerformIO $
      withCString "ReferenceRect" $
        \ clsNamePtr ->
          withCString "set_border_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReferenceRect_set_border_color #-}

instance Method "set_border_color" GodotReferenceRect
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReferenceRect_set_border_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotColorPicker = GodotColorPicker GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotColorPicker where
        type BaseClass GodotColorPicker = GodotBoxContainer
        super = coerce
bindColorPicker_set_pick_color
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "set_pick_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_set_pick_color #-}

instance Method "set_pick_color" GodotColorPicker
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_set_pick_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_get_pick_color
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "get_pick_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_get_pick_color #-}

instance Method "get_pick_color" GodotColorPicker (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_get_pick_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_set_raw_mode
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "set_raw_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_set_raw_mode #-}

instance Method "set_raw_mode" GodotColorPicker (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_set_raw_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_is_raw_mode
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "is_raw_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_is_raw_mode #-}

instance Method "is_raw_mode" GodotColorPicker (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_is_raw_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_set_deferred_mode
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "set_deferred_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_set_deferred_mode #-}

instance Method "set_deferred_mode" GodotColorPicker
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_set_deferred_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_is_deferred_mode
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "is_deferred_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_is_deferred_mode #-}

instance Method "is_deferred_mode" GodotColorPicker (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_is_deferred_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_set_edit_alpha
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "set_edit_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_set_edit_alpha #-}

instance Method "set_edit_alpha" GodotColorPicker (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_set_edit_alpha (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_is_editing_alpha
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "is_editing_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_is_editing_alpha #-}

instance Method "is_editing_alpha" GodotColorPicker (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_is_editing_alpha
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker_add_preset
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "add_preset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker_add_preset #-}

instance Method "add_preset" GodotColorPicker (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker_add_preset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__value_changed
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_value_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__value_changed #-}

instance Method "_value_changed" GodotColorPicker (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__value_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__html_entered
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_html_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__html_entered #-}

instance Method "_html_entered" GodotColorPicker
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__html_entered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__text_type_toggled
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_text_type_toggled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__text_type_toggled #-}

instance Method "_text_type_toggled" GodotColorPicker (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__text_type_toggled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__add_preset_pressed
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_add_preset_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__add_preset_pressed #-}

instance Method "_add_preset_pressed" GodotColorPicker (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__add_preset_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__screen_pick_pressed
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_screen_pick_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__screen_pick_pressed #-}

instance Method "_screen_pick_pressed" GodotColorPicker (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__screen_pick_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__sample_draw
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_sample_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__sample_draw #-}

instance Method "_sample_draw" GodotColorPicker (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__sample_draw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__update_presets
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_update_presets" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__update_presets #-}

instance Method "_update_presets" GodotColorPicker (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__update_presets (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__hsv_draw
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_hsv_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__hsv_draw #-}

instance Method "_hsv_draw" GodotColorPicker
           (Int -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__hsv_draw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__uv_input
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_uv_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__uv_input #-}

instance Method "_uv_input" GodotColorPicker
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__uv_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__w_input
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_w_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__w_input #-}

instance Method "_w_input" GodotColorPicker
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__w_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__preset_input
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_preset_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__preset_input #-}

instance Method "_preset_input" GodotColorPicker
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__preset_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__screen_input
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_screen_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__screen_input #-}

instance Method "_screen_input" GodotColorPicker
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__screen_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__focus_enter
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_focus_enter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__focus_enter #-}

instance Method "_focus_enter" GodotColorPicker (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__focus_enter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__focus_exit
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_focus_exit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__focus_exit #-}

instance Method "_focus_exit" GodotColorPicker (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__focus_exit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPicker__html_focus_exit
  = unsafePerformIO $
      withCString "ColorPicker" $
        \ clsNamePtr ->
          withCString "_html_focus_exit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPicker__html_focus_exit #-}

instance Method "_html_focus_exit" GodotColorPicker (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPicker__html_focus_exit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotColorPickerButton = GodotColorPickerButton GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotColorPickerButton where
        type BaseClass GodotColorPickerButton = GodotButton
        super = coerce
bindColorPickerButton_set_pick_color
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "set_pick_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton_set_pick_color #-}

instance Method "set_pick_color" GodotColorPickerButton
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton_set_pick_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPickerButton_get_pick_color
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "get_pick_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton_get_pick_color #-}

instance Method "get_pick_color" GodotColorPickerButton
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton_get_pick_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPickerButton_get_picker
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "get_picker" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton_get_picker #-}

instance Method "get_picker" GodotColorPickerButton
           (IO GodotColorPicker)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton_get_picker
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPickerButton_get_popup
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "get_popup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton_get_popup #-}

instance Method "get_popup" GodotColorPickerButton
           (IO GodotPopupPanel)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton_get_popup (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPickerButton_set_edit_alpha
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "set_edit_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton_set_edit_alpha #-}

instance Method "set_edit_alpha" GodotColorPickerButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton_set_edit_alpha
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPickerButton_is_editing_alpha
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "is_editing_alpha" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton_is_editing_alpha #-}

instance Method "is_editing_alpha" GodotColorPickerButton (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton_is_editing_alpha
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPickerButton__color_changed
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "_color_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton__color_changed #-}

instance Method "_color_changed" GodotColorPickerButton
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton__color_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindColorPickerButton__modal_closed
  = unsafePerformIO $
      withCString "ColorPickerButton" $
        \ clsNamePtr ->
          withCString "_modal_closed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindColorPickerButton__modal_closed #-}

instance Method "_modal_closed" GodotColorPickerButton (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindColorPickerButton__modal_closed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRichTextLabel = GodotRichTextLabel GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotRichTextLabel where
        type BaseClass GodotRichTextLabel = GodotControl
        super = coerce
bindRichTextLabel__gui_input
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel__gui_input #-}

instance Method "_gui_input" GodotRichTextLabel
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel__gui_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel__scroll_changed
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "_scroll_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel__scroll_changed #-}

instance Method "_scroll_changed" GodotRichTextLabel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel__scroll_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_text
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_text #-}

instance Method "get_text" GodotRichTextLabel (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_add_text
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "add_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_add_text #-}

instance Method "add_text" GodotRichTextLabel
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_add_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_text
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_text #-}

instance Method "set_text" GodotRichTextLabel
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_text (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_add_image
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "add_image" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_add_image #-}

instance Method "add_image" GodotRichTextLabel
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_add_image (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_newline
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "newline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_newline #-}

instance Method "newline" GodotRichTextLabel (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_newline (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_remove_line
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "remove_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_remove_line #-}

instance Method "remove_line" GodotRichTextLabel (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_remove_line (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_font
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_font" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_font #-}

instance Method "push_font" GodotRichTextLabel (GodotFont -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_font (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_color
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_color #-}

instance Method "push_color" GodotRichTextLabel
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_align
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_align #-}

instance Method "push_align" GodotRichTextLabel (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_align (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_indent
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_indent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_indent #-}

instance Method "push_indent" GodotRichTextLabel (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_indent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_list
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_list #-}

instance Method "push_list" GodotRichTextLabel (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_meta
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_meta #-}

instance Method "push_meta" GodotRichTextLabel
           (GodotVariant -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_meta (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_underline
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_underline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_underline #-}

instance Method "push_underline" GodotRichTextLabel (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_underline
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_strikethrough
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_strikethrough" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_strikethrough #-}

instance Method "push_strikethrough" GodotRichTextLabel (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_strikethrough
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_table
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_table" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_table #-}

instance Method "push_table" GodotRichTextLabel (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_table (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_table_column_expand
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_table_column_expand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_table_column_expand #-}

instance Method "set_table_column_expand" GodotRichTextLabel
           (Int -> Bool -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_table_column_expand
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_push_cell
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "push_cell" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_push_cell #-}

instance Method "push_cell" GodotRichTextLabel (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_push_cell (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_pop
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "pop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_pop #-}

instance Method "pop" GodotRichTextLabel (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_pop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_clear
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_clear #-}

instance Method "clear" GodotRichTextLabel (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_meta_underline
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_meta_underline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_meta_underline #-}

instance Method "set_meta_underline" GodotRichTextLabel
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_meta_underline
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_is_meta_underlined
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "is_meta_underlined" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_is_meta_underlined #-}

instance Method "is_meta_underlined" GodotRichTextLabel (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_is_meta_underlined
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_override_selected_font_color
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_override_selected_font_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_override_selected_font_color #-}

instance Method "set_override_selected_font_color"
           GodotRichTextLabel
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRichTextLabel_set_override_selected_font_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_is_overriding_selected_font_color
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "is_overriding_selected_font_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_is_overriding_selected_font_color
             #-}

instance Method "is_overriding_selected_font_color"
           GodotRichTextLabel
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRichTextLabel_is_overriding_selected_font_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_scroll_active
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_scroll_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_scroll_active #-}

instance Method "set_scroll_active" GodotRichTextLabel
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_scroll_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_is_scroll_active
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "is_scroll_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_is_scroll_active #-}

instance Method "is_scroll_active" GodotRichTextLabel (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_is_scroll_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_scroll_follow
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_scroll_follow" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_scroll_follow #-}

instance Method "set_scroll_follow" GodotRichTextLabel
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_scroll_follow
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_is_scroll_following
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "is_scroll_following" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_is_scroll_following #-}

instance Method "is_scroll_following" GodotRichTextLabel (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_is_scroll_following
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_v_scroll
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_v_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_v_scroll #-}

instance Method "get_v_scroll" GodotRichTextLabel
           (IO GodotVScrollBar)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_v_scroll (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_scroll_to_line
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "scroll_to_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_scroll_to_line #-}

instance Method "scroll_to_line" GodotRichTextLabel (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_scroll_to_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_tab_size
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_tab_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_tab_size #-}

instance Method "set_tab_size" GodotRichTextLabel (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_tab_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_tab_size
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_tab_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_tab_size #-}

instance Method "get_tab_size" GodotRichTextLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_tab_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_selection_enabled
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_selection_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_selection_enabled #-}

instance Method "set_selection_enabled" GodotRichTextLabel
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_selection_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_is_selection_enabled
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "is_selection_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_is_selection_enabled #-}

instance Method "is_selection_enabled" GodotRichTextLabel (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_is_selection_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_parse_bbcode
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "parse_bbcode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_parse_bbcode #-}

instance Method "parse_bbcode" GodotRichTextLabel
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_parse_bbcode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_append_bbcode
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "append_bbcode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_append_bbcode #-}

instance Method "append_bbcode" GodotRichTextLabel
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_append_bbcode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_bbcode
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_bbcode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_bbcode #-}

instance Method "set_bbcode" GodotRichTextLabel
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_bbcode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_bbcode
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_bbcode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_bbcode #-}

instance Method "get_bbcode" GodotRichTextLabel (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_bbcode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_visible_characters
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_visible_characters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_visible_characters #-}

instance Method "set_visible_characters" GodotRichTextLabel
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_visible_characters
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_visible_characters
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_visible_characters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_visible_characters #-}

instance Method "get_visible_characters" GodotRichTextLabel
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_visible_characters
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_percent_visible
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_percent_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_percent_visible #-}

instance Method "set_percent_visible" GodotRichTextLabel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_percent_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_percent_visible
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_percent_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_percent_visible #-}

instance Method "get_percent_visible" GodotRichTextLabel (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_percent_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_total_character_count
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_total_character_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_total_character_count #-}

instance Method "get_total_character_count" GodotRichTextLabel
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_total_character_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_set_use_bbcode
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "set_use_bbcode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_set_use_bbcode #-}

instance Method "set_use_bbcode" GodotRichTextLabel (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_set_use_bbcode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_is_using_bbcode
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "is_using_bbcode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_is_using_bbcode #-}

instance Method "is_using_bbcode" GodotRichTextLabel (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_is_using_bbcode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_line_count
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_line_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_line_count #-}

instance Method "get_line_count" GodotRichTextLabel (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_line_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_visible_line_count
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_visible_line_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_visible_line_count #-}

instance Method "get_visible_line_count" GodotRichTextLabel
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_visible_line_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRichTextLabel_get_content_height
  = unsafePerformIO $
      withCString "RichTextLabel" $
        \ clsNamePtr ->
          withCString "get_content_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRichTextLabel_get_content_height #-}

instance Method "get_content_height" GodotRichTextLabel (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRichTextLabel_get_content_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMarginContainer = GodotMarginContainer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotMarginContainer where
        type BaseClass GodotMarginContainer = GodotContainer
        super = coerce

newtype GodotPopupDialog = GodotPopupDialog GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotPopupDialog where
        type BaseClass GodotPopupDialog = GodotPopup
        super = coerce

newtype GodotViewportContainer = GodotViewportContainer GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotViewportContainer where
        type BaseClass GodotViewportContainer = GodotContainer
        super = coerce
bindViewportContainer__input
  = unsafePerformIO $
      withCString "ViewportContainer" $
        \ clsNamePtr ->
          withCString "_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewportContainer__input #-}

instance Method "_input" GodotViewportContainer
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewportContainer__input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewportContainer_set_stretch
  = unsafePerformIO $
      withCString "ViewportContainer" $
        \ clsNamePtr ->
          withCString "set_stretch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewportContainer_set_stretch #-}

instance Method "set_stretch" GodotViewportContainer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewportContainer_set_stretch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewportContainer_is_stretch_enabled
  = unsafePerformIO $
      withCString "ViewportContainer" $
        \ clsNamePtr ->
          withCString "is_stretch_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewportContainer_is_stretch_enabled #-}

instance Method "is_stretch_enabled" GodotViewportContainer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewportContainer_is_stretch_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewportContainer_set_stretch_shrink
  = unsafePerformIO $
      withCString "ViewportContainer" $
        \ clsNamePtr ->
          withCString "set_stretch_shrink" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewportContainer_set_stretch_shrink #-}

instance Method "set_stretch_shrink" GodotViewportContainer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewportContainer_set_stretch_shrink
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindViewportContainer_get_stretch_shrink
  = unsafePerformIO $
      withCString "ViewportContainer" $
        \ clsNamePtr ->
          withCString "get_stretch_shrink" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindViewportContainer_get_stretch_shrink #-}

instance Method "get_stretch_shrink" GodotViewportContainer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindViewportContainer_get_stretch_shrink
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSplitContainer = GodotSplitContainer GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotSplitContainer where
        type BaseClass GodotSplitContainer = GodotContainer
        super = coerce
bindSplitContainer__gui_input
  = unsafePerformIO $
      withCString "SplitContainer" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSplitContainer__gui_input #-}

instance Method "_gui_input" GodotSplitContainer
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSplitContainer__gui_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSplitContainer_set_split_offset
  = unsafePerformIO $
      withCString "SplitContainer" $
        \ clsNamePtr ->
          withCString "set_split_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSplitContainer_set_split_offset #-}

instance Method "set_split_offset" GodotSplitContainer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSplitContainer_set_split_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSplitContainer_get_split_offset
  = unsafePerformIO $
      withCString "SplitContainer" $
        \ clsNamePtr ->
          withCString "get_split_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSplitContainer_get_split_offset #-}

instance Method "get_split_offset" GodotSplitContainer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSplitContainer_get_split_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSplitContainer_set_collapsed
  = unsafePerformIO $
      withCString "SplitContainer" $
        \ clsNamePtr ->
          withCString "set_collapsed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSplitContainer_set_collapsed #-}

instance Method "set_collapsed" GodotSplitContainer (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSplitContainer_set_collapsed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSplitContainer_is_collapsed
  = unsafePerformIO $
      withCString "SplitContainer" $
        \ clsNamePtr ->
          withCString "is_collapsed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSplitContainer_is_collapsed #-}

instance Method "is_collapsed" GodotSplitContainer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSplitContainer_is_collapsed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSplitContainer_set_dragger_visibility
  = unsafePerformIO $
      withCString "SplitContainer" $
        \ clsNamePtr ->
          withCString "set_dragger_visibility" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSplitContainer_set_dragger_visibility #-}

instance Method "set_dragger_visibility" GodotSplitContainer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSplitContainer_set_dragger_visibility
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSplitContainer_get_dragger_visibility
  = unsafePerformIO $
      withCString "SplitContainer" $
        \ clsNamePtr ->
          withCString "get_dragger_visibility" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSplitContainer_get_dragger_visibility #-}

instance Method "get_dragger_visibility" GodotSplitContainer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSplitContainer_get_dragger_visibility
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotHSplitContainer = GodotHSplitContainer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotHSplitContainer where
        type BaseClass GodotHSplitContainer = GodotSplitContainer
        super = coerce

newtype GodotVSplitContainer = GodotVSplitContainer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotVSplitContainer where
        type BaseClass GodotVSplitContainer = GodotSplitContainer
        super = coerce

newtype GodotGraphNode = GodotGraphNode GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotGraphNode where
        type BaseClass GodotGraphNode = GodotContainer
        super = coerce
bindGraphNode_set_title
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_title #-}

instance Method "set_title" GodotGraphNode (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_title (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_title
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_title #-}

instance Method "get_title" GodotGraphNode (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_title (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode__gui_input
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode__gui_input #-}

instance Method "_gui_input" GodotGraphNode
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_set_slot
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_slot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_slot #-}

instance Method "set_slot" GodotGraphNode
           (Int ->
              Bool ->
                Int ->
                  GodotColor ->
                    Bool -> Int -> GodotColor -> GodotTexture -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_slot (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_clear_slot
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "clear_slot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_clear_slot #-}

instance Method "clear_slot" GodotGraphNode (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_clear_slot (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_clear_all_slots
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "clear_all_slots" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_clear_all_slots #-}

instance Method "clear_all_slots" GodotGraphNode (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_clear_all_slots (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_is_slot_enabled_left
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "is_slot_enabled_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_is_slot_enabled_left #-}

instance Method "is_slot_enabled_left" GodotGraphNode
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_is_slot_enabled_left
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_slot_type_left
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_slot_type_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_slot_type_left #-}

instance Method "get_slot_type_left" GodotGraphNode (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_slot_type_left
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_slot_color_left
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_slot_color_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_slot_color_left #-}

instance Method "get_slot_color_left" GodotGraphNode
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_slot_color_left
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_is_slot_enabled_right
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "is_slot_enabled_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_is_slot_enabled_right #-}

instance Method "is_slot_enabled_right" GodotGraphNode
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_is_slot_enabled_right
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_slot_type_right
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_slot_type_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_slot_type_right #-}

instance Method "get_slot_type_right" GodotGraphNode
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_slot_type_right
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_slot_color_right
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_slot_color_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_slot_color_right #-}

instance Method "get_slot_color_right" GodotGraphNode
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_slot_color_right
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_set_offset
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_offset #-}

instance Method "set_offset" GodotGraphNode (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_offset
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_offset #-}

instance Method "get_offset" GodotGraphNode (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_set_comment
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_comment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_comment #-}

instance Method "set_comment" GodotGraphNode (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_comment (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_is_comment
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "is_comment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_is_comment #-}

instance Method "is_comment" GodotGraphNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_is_comment (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_set_resizable
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_resizable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_resizable #-}

instance Method "set_resizable" GodotGraphNode (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_resizable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_is_resizable
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "is_resizable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_is_resizable #-}

instance Method "is_resizable" GodotGraphNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_is_resizable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_set_selected
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_selected #-}

instance Method "set_selected" GodotGraphNode (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_is_selected
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "is_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_is_selected #-}

instance Method "is_selected" GodotGraphNode (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_is_selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_output_count
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_output_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_output_count #-}

instance Method "get_connection_output_count" GodotGraphNode
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_output_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_input_count
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_input_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_input_count #-}

instance Method "get_connection_input_count" GodotGraphNode
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_input_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_output_position
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_output_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_output_position #-}

instance Method "get_connection_output_position" GodotGraphNode
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_output_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_output_type
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_output_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_output_type #-}

instance Method "get_connection_output_type" GodotGraphNode
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_output_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_output_color
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_output_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_output_color #-}

instance Method "get_connection_output_color" GodotGraphNode
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_output_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_input_position
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_input_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_input_position #-}

instance Method "get_connection_input_position" GodotGraphNode
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_input_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_input_type
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_input_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_input_type #-}

instance Method "get_connection_input_type" GodotGraphNode
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_input_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_connection_input_color
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_connection_input_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_connection_input_color #-}

instance Method "get_connection_input_color" GodotGraphNode
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_connection_input_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_set_show_close_button
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_show_close_button" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_show_close_button #-}

instance Method "set_show_close_button" GodotGraphNode
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_show_close_button
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_is_close_button_visible
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "is_close_button_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_is_close_button_visible #-}

instance Method "is_close_button_visible" GodotGraphNode (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_is_close_button_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_set_overlay
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "set_overlay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_set_overlay #-}

instance Method "set_overlay" GodotGraphNode (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_set_overlay (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphNode_get_overlay
  = unsafePerformIO $
      withCString "GraphNode" $
        \ clsNamePtr ->
          withCString "get_overlay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphNode_get_overlay #-}

instance Method "get_overlay" GodotGraphNode (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphNode_get_overlay (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGraphEdit = GodotGraphEdit GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotGraphEdit where
        type BaseClass GodotGraphEdit = GodotControl
        super = coerce
bindGraphEdit_connect_node
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "connect_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_connect_node #-}

instance Method "connect_node" GodotGraphEdit
           (GodotString -> Int -> GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_connect_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_is_node_connected
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "is_node_connected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_is_node_connected #-}

instance Method "is_node_connected" GodotGraphEdit
           (GodotString -> Int -> GodotString -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_is_node_connected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_disconnect_node
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "disconnect_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_disconnect_node #-}

instance Method "disconnect_node" GodotGraphEdit
           (GodotString -> Int -> GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_disconnect_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_set_connection_activity
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "set_connection_activity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_set_connection_activity #-}

instance Method "set_connection_activity" GodotGraphEdit
           (GodotString -> Int -> GodotString -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_set_connection_activity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_get_connection_list
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "get_connection_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_get_connection_list #-}

instance Method "get_connection_list" GodotGraphEdit
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_get_connection_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_clear_connections
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "clear_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_clear_connections #-}

instance Method "clear_connections" GodotGraphEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_clear_connections (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_get_scroll_ofs
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "get_scroll_ofs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_get_scroll_ofs #-}

instance Method "get_scroll_ofs" GodotGraphEdit (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_get_scroll_ofs (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_set_scroll_ofs
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "set_scroll_ofs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_set_scroll_ofs #-}

instance Method "set_scroll_ofs" GodotGraphEdit
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_set_scroll_ofs (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_add_valid_right_disconnect_type
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "add_valid_right_disconnect_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_add_valid_right_disconnect_type #-}

instance Method "add_valid_right_disconnect_type" GodotGraphEdit
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindGraphEdit_add_valid_right_disconnect_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_remove_valid_right_disconnect_type
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "remove_valid_right_disconnect_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_remove_valid_right_disconnect_type #-}

instance Method "remove_valid_right_disconnect_type" GodotGraphEdit
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindGraphEdit_remove_valid_right_disconnect_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_add_valid_left_disconnect_type
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "add_valid_left_disconnect_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_add_valid_left_disconnect_type #-}

instance Method "add_valid_left_disconnect_type" GodotGraphEdit
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_add_valid_left_disconnect_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_remove_valid_left_disconnect_type
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "remove_valid_left_disconnect_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_remove_valid_left_disconnect_type #-}

instance Method "remove_valid_left_disconnect_type" GodotGraphEdit
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindGraphEdit_remove_valid_left_disconnect_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_add_valid_connection_type
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "add_valid_connection_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_add_valid_connection_type #-}

instance Method "add_valid_connection_type" GodotGraphEdit
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_add_valid_connection_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_remove_valid_connection_type
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "remove_valid_connection_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_remove_valid_connection_type #-}

instance Method "remove_valid_connection_type" GodotGraphEdit
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_remove_valid_connection_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_is_valid_connection_type
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "is_valid_connection_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_is_valid_connection_type #-}

instance Method "is_valid_connection_type" GodotGraphEdit
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_is_valid_connection_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_set_zoom
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "set_zoom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_set_zoom #-}

instance Method "set_zoom" GodotGraphEdit (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_set_zoom (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_get_zoom
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "get_zoom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_get_zoom #-}

instance Method "get_zoom" GodotGraphEdit (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_get_zoom (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_set_snap
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "set_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_set_snap #-}

instance Method "set_snap" GodotGraphEdit (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_set_snap (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_get_snap
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "get_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_get_snap #-}

instance Method "get_snap" GodotGraphEdit (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_get_snap (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_set_use_snap
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "set_use_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_set_use_snap #-}

instance Method "set_use_snap" GodotGraphEdit (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_set_use_snap (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_is_using_snap
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "is_using_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_is_using_snap #-}

instance Method "is_using_snap" GodotGraphEdit (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_is_using_snap (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_set_right_disconnects
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "set_right_disconnects" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_set_right_disconnects #-}

instance Method "set_right_disconnects" GodotGraphEdit
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_set_right_disconnects
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_is_right_disconnects_enabled
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "is_right_disconnects_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_is_right_disconnects_enabled #-}

instance Method "is_right_disconnects_enabled" GodotGraphEdit
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_is_right_disconnects_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__graph_node_moved
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_graph_node_moved" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__graph_node_moved #-}

instance Method "_graph_node_moved" GodotGraphEdit
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__graph_node_moved (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__graph_node_raised
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_graph_node_raised" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__graph_node_raised #-}

instance Method "_graph_node_raised" GodotGraphEdit
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__graph_node_raised
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__top_layer_input
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_top_layer_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__top_layer_input #-}

instance Method "_top_layer_input" GodotGraphEdit
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__top_layer_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__top_layer_draw
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_top_layer_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__top_layer_draw #-}

instance Method "_top_layer_draw" GodotGraphEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__top_layer_draw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__scroll_moved
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_scroll_moved" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__scroll_moved #-}

instance Method "_scroll_moved" GodotGraphEdit (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__scroll_moved (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__zoom_minus
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_zoom_minus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__zoom_minus #-}

instance Method "_zoom_minus" GodotGraphEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__zoom_minus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__zoom_reset
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_zoom_reset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__zoom_reset #-}

instance Method "_zoom_reset" GodotGraphEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__zoom_reset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__zoom_plus
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_zoom_plus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__zoom_plus #-}

instance Method "_zoom_plus" GodotGraphEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__zoom_plus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__snap_toggled
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_snap_toggled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__snap_toggled #-}

instance Method "_snap_toggled" GodotGraphEdit (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__snap_toggled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__snap_value_changed
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_snap_value_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__snap_value_changed #-}

instance Method "_snap_value_changed" GodotGraphEdit
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__snap_value_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__gui_input
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__gui_input #-}

instance Method "_gui_input" GodotGraphEdit
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__gui_input (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__update_scroll_offset
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_update_scroll_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__update_scroll_offset #-}

instance Method "_update_scroll_offset" GodotGraphEdit (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__update_scroll_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit__connections_layer_draw
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "_connections_layer_draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit__connections_layer_draw #-}

instance Method "_connections_layer_draw" GodotGraphEdit (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit__connections_layer_draw
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_get_zoom_hbox
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "get_zoom_hbox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_get_zoom_hbox #-}

instance Method "get_zoom_hbox" GodotGraphEdit
           (IO GodotHBoxContainer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_get_zoom_hbox (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGraphEdit_set_selected
  = unsafePerformIO $
      withCString "GraphEdit" $
        \ clsNamePtr ->
          withCString "set_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGraphEdit_set_selected #-}

instance Method "set_selected" GodotGraphEdit
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGraphEdit_set_selected (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpatial = GodotSpatial GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotSpatial where
        type BaseClass GodotSpatial = GodotNode
        super = coerce
bindSpatial_set_transform
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_transform #-}

instance Method "set_transform" GodotSpatial
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_transform
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_transform #-}

instance Method "get_transform" GodotSpatial (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_translation
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_translation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_translation #-}

instance Method "set_translation" GodotSpatial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_translation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_translation
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_translation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_translation #-}

instance Method "get_translation" GodotSpatial (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_translation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_rotation
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_rotation #-}

instance Method "set_rotation" GodotSpatial (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_rotation (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_rotation
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_rotation #-}

instance Method "get_rotation" GodotSpatial (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_rotation (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_rotation_degrees
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_rotation_degrees #-}

instance Method "set_rotation_degrees" GodotSpatial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_rotation_degrees
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_rotation_degrees #-}

instance Method "get_rotation_degrees" GodotSpatial
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_scale
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_scale #-}

instance Method "set_scale" GodotSpatial (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_scale (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_scale
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_scale #-}

instance Method "get_scale" GodotSpatial (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_scale (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_global_transform
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_global_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_global_transform #-}

instance Method "set_global_transform" GodotSpatial
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_global_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_global_transform
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_global_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_global_transform #-}

instance Method "get_global_transform" GodotSpatial
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_global_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_parent_spatial
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_parent_spatial" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_parent_spatial #-}

instance Method "get_parent_spatial" GodotSpatial (IO GodotSpatial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_parent_spatial (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_ignore_transform_notification
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_ignore_transform_notification" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_ignore_transform_notification #-}

instance Method "set_ignore_transform_notification" GodotSpatial
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatial_set_ignore_transform_notification
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_as_toplevel
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_as_toplevel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_as_toplevel #-}

instance Method "set_as_toplevel" GodotSpatial (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_as_toplevel (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_is_set_as_toplevel
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "is_set_as_toplevel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_is_set_as_toplevel #-}

instance Method "is_set_as_toplevel" GodotSpatial (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_is_set_as_toplevel (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_disable_scale
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_disable_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_disable_scale #-}

instance Method "set_disable_scale" GodotSpatial (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_disable_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_is_scale_disabled
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "is_scale_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_is_scale_disabled #-}

instance Method "is_scale_disabled" GodotSpatial (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_is_scale_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_world
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_world #-}

instance Method "get_world" GodotSpatial (IO GodotWorld) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_world (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_force_update_transform
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "force_update_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_force_update_transform #-}

instance Method "force_update_transform" GodotSpatial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_force_update_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial__update_gizmo
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "_update_gizmo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial__update_gizmo #-}

instance Method "_update_gizmo" GodotSpatial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial__update_gizmo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_update_gizmo
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "update_gizmo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_update_gizmo #-}

instance Method "update_gizmo" GodotSpatial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_update_gizmo (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_gizmo
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_gizmo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_gizmo #-}

instance Method "set_gizmo" GodotSpatial
           (GodotSpatialGizmo -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_gizmo (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_get_gizmo
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "get_gizmo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_get_gizmo #-}

instance Method "get_gizmo" GodotSpatial (IO GodotSpatialGizmo)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_get_gizmo (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_visible
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_visible #-}

instance Method "set_visible" GodotSpatial (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_visible (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_is_visible
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "is_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_is_visible #-}

instance Method "is_visible" GodotSpatial (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_is_visible (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_is_visible_in_tree
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "is_visible_in_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_is_visible_in_tree #-}

instance Method "is_visible_in_tree" GodotSpatial (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_is_visible_in_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_show
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "show" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_show #-}

instance Method "show" GodotSpatial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_show (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_hide
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "hide" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_hide #-}

instance Method "hide" GodotSpatial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_hide (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_notify_local_transform
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_notify_local_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_notify_local_transform #-}

instance Method "set_notify_local_transform" GodotSpatial
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_notify_local_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_is_local_transform_notification_enabled
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "is_local_transform_notification_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_is_local_transform_notification_enabled
             #-}

instance Method "is_local_transform_notification_enabled"
           GodotSpatial
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatial_is_local_transform_notification_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_notify_transform
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_notify_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_notify_transform #-}

instance Method "set_notify_transform" GodotSpatial (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_notify_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_is_transform_notification_enabled
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "is_transform_notification_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_is_transform_notification_enabled #-}

instance Method "is_transform_notification_enabled" GodotSpatial
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatial_is_transform_notification_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_rotate
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "rotate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_rotate #-}

instance Method "rotate" GodotSpatial
           (GodotVector3 -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_rotate (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_global_rotate
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "global_rotate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_global_rotate #-}

instance Method "global_rotate" GodotSpatial
           (GodotVector3 -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_global_rotate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_global_scale
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "global_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_global_scale #-}

instance Method "global_scale" GodotSpatial (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_global_scale (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_global_translate
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "global_translate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_global_translate #-}

instance Method "global_translate" GodotSpatial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_global_translate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_rotate_object_local
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "rotate_object_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_rotate_object_local #-}

instance Method "rotate_object_local" GodotSpatial
           (GodotVector3 -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_rotate_object_local (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_scale_object_local
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "scale_object_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_scale_object_local #-}

instance Method "scale_object_local" GodotSpatial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_scale_object_local (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_translate_object_local
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "translate_object_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_translate_object_local #-}

instance Method "translate_object_local" GodotSpatial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_translate_object_local
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_rotate_x
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "rotate_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_rotate_x #-}

instance Method "rotate_x" GodotSpatial (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_rotate_x (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_rotate_y
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "rotate_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_rotate_y #-}

instance Method "rotate_y" GodotSpatial (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_rotate_y (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_rotate_z
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "rotate_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_rotate_z #-}

instance Method "rotate_z" GodotSpatial (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_rotate_z (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_translate
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "translate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_translate #-}

instance Method "translate" GodotSpatial (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_translate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_orthonormalize
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "orthonormalize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_orthonormalize #-}

instance Method "orthonormalize" GodotSpatial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_orthonormalize (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_set_identity
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "set_identity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_set_identity #-}

instance Method "set_identity" GodotSpatial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_set_identity (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_look_at
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "look_at" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_look_at #-}

instance Method "look_at" GodotSpatial
           (GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_look_at (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_look_at_from_position
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "look_at_from_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_look_at_from_position #-}

instance Method "look_at_from_position" GodotSpatial
           (GodotVector3 -> GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_look_at_from_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_to_local
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "to_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_to_local #-}

instance Method "to_local" GodotSpatial
           (GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_to_local (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatial_to_global
  = unsafePerformIO $
      withCString "Spatial" $
        \ clsNamePtr ->
          withCString "to_global" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatial_to_global #-}

instance Method "to_global" GodotSpatial
           (GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatial_to_global (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpatialGizmo = GodotSpatialGizmo GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotSpatialGizmo where
        type BaseClass GodotSpatialGizmo = GodotReference
        super = coerce

newtype GodotSkeleton = GodotSkeleton GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotSkeleton where
        type BaseClass GodotSkeleton = GodotSpatial
        super = coerce
bindSkeleton_add_bone
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "add_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_add_bone #-}

instance Method "add_bone" GodotSkeleton (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_add_bone (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_find_bone
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "find_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_find_bone #-}

instance Method "find_bone" GodotSkeleton (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_find_bone (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_name
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_name #-}

instance Method "get_bone_name" GodotSkeleton
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_parent
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_parent #-}

instance Method "get_bone_parent" GodotSkeleton (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_parent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_set_bone_parent
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "set_bone_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_set_bone_parent #-}

instance Method "set_bone_parent" GodotSkeleton
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_set_bone_parent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_count
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_count #-}

instance Method "get_bone_count" GodotSkeleton (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_unparent_bone_and_rest
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "unparent_bone_and_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_unparent_bone_and_rest #-}

instance Method "unparent_bone_and_rest" GodotSkeleton
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_unparent_bone_and_rest
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_rest
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_rest #-}

instance Method "get_bone_rest" GodotSkeleton
           (Int -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_rest (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_set_bone_rest
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "set_bone_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_set_bone_rest #-}

instance Method "set_bone_rest" GodotSkeleton
           (Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_set_bone_rest (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_set_bone_disable_rest
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "set_bone_disable_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_set_bone_disable_rest #-}

instance Method "set_bone_disable_rest" GodotSkeleton
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_set_bone_disable_rest
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_is_bone_rest_disabled
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "is_bone_rest_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_is_bone_rest_disabled #-}

instance Method "is_bone_rest_disabled" GodotSkeleton
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_is_bone_rest_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_bind_child_node_to_bone
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "bind_child_node_to_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_bind_child_node_to_bone #-}

instance Method "bind_child_node_to_bone" GodotSkeleton
           (Int -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_bind_child_node_to_bone
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_unbind_child_node_from_bone
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "unbind_child_node_from_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_unbind_child_node_from_bone #-}

instance Method "unbind_child_node_from_bone" GodotSkeleton
           (Int -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_unbind_child_node_from_bone
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bound_child_nodes_to_bone
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bound_child_nodes_to_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bound_child_nodes_to_bone #-}

instance Method "get_bound_child_nodes_to_bone" GodotSkeleton
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bound_child_nodes_to_bone
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_clear_bones
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "clear_bones" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_clear_bones #-}

instance Method "clear_bones" GodotSkeleton (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_clear_bones (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_pose
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_pose" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_pose #-}

instance Method "get_bone_pose" GodotSkeleton
           (Int -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_pose (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_set_bone_pose
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "set_bone_pose" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_set_bone_pose #-}

instance Method "set_bone_pose" GodotSkeleton
           (Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_set_bone_pose (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_set_bone_global_pose
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "set_bone_global_pose" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_set_bone_global_pose #-}

instance Method "set_bone_global_pose" GodotSkeleton
           (Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_set_bone_global_pose
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_global_pose
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_global_pose" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_global_pose #-}

instance Method "get_bone_global_pose" GodotSkeleton
           (Int -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_global_pose
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_custom_pose
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_custom_pose" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_custom_pose #-}

instance Method "get_bone_custom_pose" GodotSkeleton
           (Int -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_custom_pose
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_set_bone_custom_pose
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "set_bone_custom_pose" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_set_bone_custom_pose #-}

instance Method "set_bone_custom_pose" GodotSkeleton
           (Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_set_bone_custom_pose
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_get_bone_transform
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "get_bone_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_get_bone_transform #-}

instance Method "get_bone_transform" GodotSkeleton
           (Int -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_get_bone_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_physical_bones_stop_simulation
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "physical_bones_stop_simulation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_physical_bones_stop_simulation #-}

instance Method "physical_bones_stop_simulation" GodotSkeleton
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_physical_bones_stop_simulation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_physical_bones_start_simulation
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "physical_bones_start_simulation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_physical_bones_start_simulation #-}

instance Method "physical_bones_start_simulation" GodotSkeleton
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_physical_bones_start_simulation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_physical_bones_add_collision_exception
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "physical_bones_add_collision_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_physical_bones_add_collision_exception
             #-}

instance Method "physical_bones_add_collision_exception"
           GodotSkeleton
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSkeleton_physical_bones_add_collision_exception
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_physical_bones_remove_collision_exception
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "physical_bones_remove_collision_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_physical_bones_remove_collision_exception
             #-}

instance Method "physical_bones_remove_collision_exception"
           GodotSkeleton
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSkeleton_physical_bones_remove_collision_exception
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton_set_bone_ignore_animation
  = unsafePerformIO $
      withCString "Skeleton" $
        \ clsNamePtr ->
          withCString "set_bone_ignore_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton_set_bone_ignore_animation #-}

instance Method "set_bone_ignore_animation" GodotSkeleton
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton_set_bone_ignore_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationPlayer = GodotAnimationPlayer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotAnimationPlayer where
        type BaseClass GodotAnimationPlayer = GodotNode
        super = coerce
bindAnimationPlayer__node_removed
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "_node_removed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer__node_removed #-}

instance Method "_node_removed" GodotAnimationPlayer
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer__node_removed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer__animation_changed
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "_animation_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer__animation_changed #-}

instance Method "_animation_changed" GodotAnimationPlayer (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer__animation_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_add_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "add_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_add_animation #-}

instance Method "add_animation" GodotAnimationPlayer
           (GodotString -> GodotAnimation -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_add_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_remove_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "remove_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_remove_animation #-}

instance Method "remove_animation" GodotAnimationPlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_remove_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_rename_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "rename_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_rename_animation #-}

instance Method "rename_animation" GodotAnimationPlayer
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_rename_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_has_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "has_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_has_animation #-}

instance Method "has_animation" GodotAnimationPlayer
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_has_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_animation #-}

instance Method "get_animation" GodotAnimationPlayer
           (GodotString -> IO GodotAnimation)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_animation_list
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_animation_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_animation_list #-}

instance Method "get_animation_list" GodotAnimationPlayer
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_animation_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_animation_set_next
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "animation_set_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_animation_set_next #-}

instance Method "animation_set_next" GodotAnimationPlayer
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_animation_set_next
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_animation_get_next
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "animation_get_next" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_animation_get_next #-}

instance Method "animation_get_next" GodotAnimationPlayer
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_animation_get_next
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_blend_time
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_blend_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_blend_time #-}

instance Method "set_blend_time" GodotAnimationPlayer
           (GodotString -> GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_blend_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_blend_time
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_blend_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_blend_time #-}

instance Method "get_blend_time" GodotAnimationPlayer
           (GodotString -> GodotString -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_blend_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_default_blend_time
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_default_blend_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_default_blend_time #-}

instance Method "set_default_blend_time" GodotAnimationPlayer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_default_blend_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_default_blend_time
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_default_blend_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_default_blend_time #-}

instance Method "get_default_blend_time" GodotAnimationPlayer
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_default_blend_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_play
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_play #-}

instance Method "play" GodotAnimationPlayer
           (GodotString -> Float -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_play (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_play_backwards
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "play_backwards" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_play_backwards #-}

instance Method "play_backwards" GodotAnimationPlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_play_backwards
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_stop
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_stop #-}

instance Method "stop" GodotAnimationPlayer (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_stop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_is_playing
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_is_playing #-}

instance Method "is_playing" GodotAnimationPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_is_playing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_current_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_current_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_current_animation #-}

instance Method "set_current_animation" GodotAnimationPlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_current_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_current_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_current_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_current_animation #-}

instance Method "get_current_animation" GodotAnimationPlayer
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_current_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_assigned_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_assigned_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_assigned_animation #-}

instance Method "set_assigned_animation" GodotAnimationPlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_assigned_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_assigned_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_assigned_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_assigned_animation #-}

instance Method "get_assigned_animation" GodotAnimationPlayer
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_assigned_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_queue
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "queue" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_queue #-}

instance Method "queue" GodotAnimationPlayer (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_queue (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_clear_queue
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "clear_queue" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_clear_queue #-}

instance Method "clear_queue" GodotAnimationPlayer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_clear_queue (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_active
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_active #-}

instance Method "set_active" GodotAnimationPlayer (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_active (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_is_active
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_is_active #-}

instance Method "is_active" GodotAnimationPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_is_active (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_speed_scale
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_speed_scale #-}

instance Method "set_speed_scale" GodotAnimationPlayer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_speed_scale
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_speed_scale #-}

instance Method "get_speed_scale" GodotAnimationPlayer (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_playing_speed
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_playing_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_playing_speed #-}

instance Method "get_playing_speed" GodotAnimationPlayer (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_playing_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_autoplay
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_autoplay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_autoplay #-}

instance Method "set_autoplay" GodotAnimationPlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_autoplay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_autoplay
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_autoplay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_autoplay #-}

instance Method "get_autoplay" GodotAnimationPlayer
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_autoplay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_root
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_root #-}

instance Method "set_root" GodotAnimationPlayer
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_set_root (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_root
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_root #-}

instance Method "get_root" GodotAnimationPlayer (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_get_root (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_find_animation
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "find_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_find_animation #-}

instance Method "find_animation" GodotAnimationPlayer
           (GodotAnimation -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_find_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_clear_caches
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "clear_caches" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_clear_caches #-}

instance Method "clear_caches" GodotAnimationPlayer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_clear_caches
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_set_animation_process_mode
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "set_animation_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_set_animation_process_mode #-}

instance Method "set_animation_process_mode" GodotAnimationPlayer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationPlayer_set_animation_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_animation_process_mode
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_animation_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_animation_process_mode #-}

instance Method "get_animation_process_mode" GodotAnimationPlayer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationPlayer_get_animation_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_current_animation_position
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_current_animation_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_current_animation_position #-}

instance Method "get_current_animation_position"
           GodotAnimationPlayer
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationPlayer_get_current_animation_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_get_current_animation_length
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "get_current_animation_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_get_current_animation_length #-}

instance Method "get_current_animation_length" GodotAnimationPlayer
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationPlayer_get_current_animation_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_seek
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_seek #-}

instance Method "seek" GodotAnimationPlayer
           (Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_seek (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationPlayer_advance
  = unsafePerformIO $
      withCString "AnimationPlayer" $
        \ clsNamePtr ->
          withCString "advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationPlayer_advance #-}

instance Method "advance" GodotAnimationPlayer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationPlayer_advance (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTween = GodotTween GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotTween where
        type BaseClass GodotTween = GodotNode
        super = coerce
bindTween_is_active
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_is_active #-}

instance Method "is_active" GodotTween (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_is_active (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_set_active
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_set_active #-}

instance Method "set_active" GodotTween (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_set_active (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_is_repeat
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "is_repeat" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_is_repeat #-}

instance Method "is_repeat" GodotTween (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_is_repeat (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_set_repeat
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "set_repeat" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_set_repeat #-}

instance Method "set_repeat" GodotTween (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_set_repeat (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_set_speed_scale
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_set_speed_scale #-}

instance Method "set_speed_scale" GodotTween (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_set_speed_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_get_speed_scale
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "get_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_get_speed_scale #-}

instance Method "get_speed_scale" GodotTween (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_get_speed_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_set_tween_process_mode
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "set_tween_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_set_tween_process_mode #-}

instance Method "set_tween_process_mode" GodotTween (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_set_tween_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_get_tween_process_mode
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "get_tween_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_get_tween_process_mode #-}

instance Method "get_tween_process_mode" GodotTween (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_get_tween_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_start
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_start #-}

instance Method "start" GodotTween (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_start (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_reset
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "reset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_reset #-}

instance Method "reset" GodotTween
           (GodotObject -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_reset (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_reset_all
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "reset_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_reset_all #-}

instance Method "reset_all" GodotTween (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_reset_all (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_stop
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_stop #-}

instance Method "stop" GodotTween
           (GodotObject -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_stop (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_stop_all
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "stop_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_stop_all #-}

instance Method "stop_all" GodotTween (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_stop_all (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_resume
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "resume" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_resume #-}

instance Method "resume" GodotTween
           (GodotObject -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_resume (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_resume_all
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "resume_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_resume_all #-}

instance Method "resume_all" GodotTween (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_resume_all (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_remove
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "remove" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_remove #-}

instance Method "remove" GodotTween
           (GodotObject -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_remove (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween__remove_by_uid
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "_remove_by_uid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween__remove_by_uid #-}

instance Method "_remove_by_uid" GodotTween (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween__remove_by_uid (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_remove_all
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "remove_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_remove_all #-}

instance Method "remove_all" GodotTween (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_remove_all (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_seek
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_seek #-}

instance Method "seek" GodotTween (Float -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_seek (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_tell
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "tell" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_tell #-}

instance Method "tell" GodotTween (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_tell (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_get_runtime
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "get_runtime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_get_runtime #-}

instance Method "get_runtime" GodotTween (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_get_runtime (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_interpolate_property
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "interpolate_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_interpolate_property #-}

instance Method "interpolate_property" GodotTween
           (GodotObject ->
              GodotNodePath ->
                GodotVariant ->
                  GodotVariant -> Float -> Int -> Int -> Float -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_interpolate_property (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_interpolate_method
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "interpolate_method" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_interpolate_method #-}

instance Method "interpolate_method" GodotTween
           (GodotObject ->
              GodotString ->
                GodotVariant ->
                  GodotVariant -> Float -> Int -> Int -> Float -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_interpolate_method (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_interpolate_callback
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "interpolate_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_interpolate_callback #-}

instance Method "interpolate_callback" GodotTween
           (GodotObject ->
              Float ->
                GodotString ->
                  GodotVariant ->
                    GodotVariant ->
                      GodotVariant -> GodotVariant -> GodotVariant -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_interpolate_callback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_interpolate_deferred_callback
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "interpolate_deferred_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_interpolate_deferred_callback #-}

instance Method "interpolate_deferred_callback" GodotTween
           (GodotObject ->
              Float ->
                GodotString ->
                  GodotVariant ->
                    GodotVariant ->
                      GodotVariant -> GodotVariant -> GodotVariant -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_interpolate_deferred_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_follow_property
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "follow_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_follow_property #-}

instance Method "follow_property" GodotTween
           (GodotObject ->
              GodotNodePath ->
                GodotVariant ->
                  GodotObject ->
                    GodotNodePath -> Float -> Int -> Int -> Float -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_follow_property (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_follow_method
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "follow_method" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_follow_method #-}

instance Method "follow_method" GodotTween
           (GodotObject ->
              GodotString ->
                GodotVariant ->
                  GodotObject ->
                    GodotString -> Float -> Int -> Int -> Float -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_follow_method (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_targeting_property
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "targeting_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_targeting_property #-}

instance Method "targeting_property" GodotTween
           (GodotObject ->
              GodotNodePath ->
                GodotObject ->
                  GodotNodePath ->
                    GodotVariant -> Float -> Int -> Int -> Float -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_targeting_property (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTween_targeting_method
  = unsafePerformIO $
      withCString "Tween" $
        \ clsNamePtr ->
          withCString "targeting_method" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTween_targeting_method #-}

instance Method "targeting_method" GodotTween
           (GodotObject ->
              GodotString ->
                GodotObject ->
                  GodotString ->
                    GodotVariant -> Float -> Int -> Int -> Float -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7, toVariant arg8,
               toVariant arg9]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTween_targeting_method (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualInstance = GodotVisualInstance GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotVisualInstance where
        type BaseClass GodotVisualInstance = GodotSpatial
        super = coerce
bindVisualInstance__get_visual_instance_rid
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "_get_visual_instance_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance__get_visual_instance_rid #-}

instance Method "_get_visual_instance_rid" GodotVisualInstance
           (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance__get_visual_instance_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualInstance_set_base
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "set_base" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance_set_base #-}

instance Method "set_base" GodotVisualInstance (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance_set_base (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualInstance_set_layer_mask
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "set_layer_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance_set_layer_mask #-}

instance Method "set_layer_mask" GodotVisualInstance (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance_set_layer_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualInstance_get_layer_mask
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "get_layer_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance_get_layer_mask #-}

instance Method "get_layer_mask" GodotVisualInstance (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance_get_layer_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualInstance_set_layer_mask_bit
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "set_layer_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance_set_layer_mask_bit #-}

instance Method "set_layer_mask_bit" GodotVisualInstance
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance_set_layer_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualInstance_get_layer_mask_bit
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "get_layer_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance_get_layer_mask_bit #-}

instance Method "get_layer_mask_bit" GodotVisualInstance
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance_get_layer_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualInstance_get_transformed_aabb
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "get_transformed_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance_get_transformed_aabb #-}

instance Method "get_transformed_aabb" GodotVisualInstance
           (IO GodotAabb)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance_get_transformed_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualInstance_get_aabb
  = unsafePerformIO $
      withCString "VisualInstance" $
        \ clsNamePtr ->
          withCString "get_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualInstance_get_aabb #-}

instance Method "get_aabb" GodotVisualInstance (IO GodotAabb) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualInstance_get_aabb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGeometryInstance = GodotGeometryInstance GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotGeometryInstance where
        type BaseClass GodotGeometryInstance = GodotVisualInstance
        super = coerce
bindGeometryInstance_set_material_override
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_material_override #-}

instance Method "set_material_override" GodotGeometryInstance
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_set_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_material_override
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_material_override #-}

instance Method "get_material_override" GodotGeometryInstance
           (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_get_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_set_flag
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_flag #-}

instance Method "set_flag" GodotGeometryInstance
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_set_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_flag
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_flag #-}

instance Method "get_flag" GodotGeometryInstance (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_get_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_set_cast_shadows_setting
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_cast_shadows_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_cast_shadows_setting #-}

instance Method "set_cast_shadows_setting" GodotGeometryInstance
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindGeometryInstance_set_cast_shadows_setting
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_cast_shadows_setting
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_cast_shadows_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_cast_shadows_setting #-}

instance Method "get_cast_shadows_setting" GodotGeometryInstance
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindGeometryInstance_get_cast_shadows_setting
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_set_lod_max_hysteresis
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_lod_max_hysteresis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_lod_max_hysteresis #-}

instance Method "set_lod_max_hysteresis" GodotGeometryInstance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_set_lod_max_hysteresis
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_lod_max_hysteresis
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_lod_max_hysteresis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_lod_max_hysteresis #-}

instance Method "get_lod_max_hysteresis" GodotGeometryInstance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_get_lod_max_hysteresis
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_set_lod_max_distance
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_lod_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_lod_max_distance #-}

instance Method "set_lod_max_distance" GodotGeometryInstance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_set_lod_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_lod_max_distance
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_lod_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_lod_max_distance #-}

instance Method "get_lod_max_distance" GodotGeometryInstance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_get_lod_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_set_lod_min_hysteresis
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_lod_min_hysteresis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_lod_min_hysteresis #-}

instance Method "set_lod_min_hysteresis" GodotGeometryInstance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_set_lod_min_hysteresis
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_lod_min_hysteresis
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_lod_min_hysteresis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_lod_min_hysteresis #-}

instance Method "get_lod_min_hysteresis" GodotGeometryInstance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_get_lod_min_hysteresis
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_set_lod_min_distance
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_lod_min_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_lod_min_distance #-}

instance Method "set_lod_min_distance" GodotGeometryInstance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_set_lod_min_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_lod_min_distance
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_lod_min_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_lod_min_distance #-}

instance Method "get_lod_min_distance" GodotGeometryInstance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_get_lod_min_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_set_extra_cull_margin
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "set_extra_cull_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_set_extra_cull_margin #-}

instance Method "set_extra_cull_margin" GodotGeometryInstance
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_set_extra_cull_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeometryInstance_get_extra_cull_margin
  = unsafePerformIO $
      withCString "GeometryInstance" $
        \ clsNamePtr ->
          withCString "get_extra_cull_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeometryInstance_get_extra_cull_margin #-}

instance Method "get_extra_cull_margin" GodotGeometryInstance
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeometryInstance_get_extra_cull_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCamera = GodotCamera GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotCamera where
        type BaseClass GodotCamera = GodotSpatial
        super = coerce
bindCamera_project_ray_normal
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "project_ray_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_project_ray_normal #-}

instance Method "project_ray_normal" GodotCamera
           (GodotVector2 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_project_ray_normal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_project_local_ray_normal
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "project_local_ray_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_project_local_ray_normal #-}

instance Method "project_local_ray_normal" GodotCamera
           (GodotVector2 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_project_local_ray_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_project_ray_origin
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "project_ray_origin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_project_ray_origin #-}

instance Method "project_ray_origin" GodotCamera
           (GodotVector2 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_project_ray_origin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_unproject_position
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "unproject_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_unproject_position #-}

instance Method "unproject_position" GodotCamera
           (GodotVector3 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_unproject_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_is_position_behind
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "is_position_behind" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_is_position_behind #-}

instance Method "is_position_behind" GodotCamera
           (GodotVector3 -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_is_position_behind (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_project_position
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "project_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_project_position #-}

instance Method "project_position" GodotCamera
           (GodotVector2 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_project_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_perspective
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_perspective" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_perspective #-}

instance Method "set_perspective" GodotCamera
           (Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_perspective (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_orthogonal
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_orthogonal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_orthogonal #-}

instance Method "set_orthogonal" GodotCamera
           (Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_orthogonal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_make_current
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "make_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_make_current #-}

instance Method "make_current" GodotCamera (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_make_current (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_clear_current
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "clear_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_clear_current #-}

instance Method "clear_current" GodotCamera (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_clear_current (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_current
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_current #-}

instance Method "set_current" GodotCamera (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_current (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_is_current
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "is_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_is_current #-}

instance Method "is_current" GodotCamera (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_is_current (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_camera_transform
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_camera_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_camera_transform #-}

instance Method "get_camera_transform" GodotCamera
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_camera_transform (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_fov
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_fov" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_fov #-}

instance Method "get_fov" GodotCamera (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_fov (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_size
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_size #-}

instance Method "get_size" GodotCamera (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_size (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_zfar
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_zfar" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_zfar #-}

instance Method "get_zfar" GodotCamera (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_zfar (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_znear
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_znear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_znear #-}

instance Method "get_znear" GodotCamera (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_znear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_fov
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_fov" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_fov #-}

instance Method "set_fov" GodotCamera (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_fov (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_size
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_size #-}

instance Method "set_size" GodotCamera (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_size (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_zfar
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_zfar" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_zfar #-}

instance Method "set_zfar" GodotCamera (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_zfar (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_znear
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_znear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_znear #-}

instance Method "set_znear" GodotCamera (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_znear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_projection
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_projection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_projection #-}

instance Method "get_projection" GodotCamera (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_projection (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_projection
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_projection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_projection #-}

instance Method "set_projection" GodotCamera (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_projection (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_h_offset
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_h_offset #-}

instance Method "set_h_offset" GodotCamera (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_h_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_h_offset
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_h_offset #-}

instance Method "get_h_offset" GodotCamera (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_h_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_v_offset
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_v_offset #-}

instance Method "set_v_offset" GodotCamera (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_v_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_v_offset
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_v_offset #-}

instance Method "get_v_offset" GodotCamera (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_v_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_cull_mask
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_cull_mask #-}

instance Method "set_cull_mask" GodotCamera (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_cull_mask (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_cull_mask
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_cull_mask #-}

instance Method "get_cull_mask" GodotCamera (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_cull_mask (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_environment
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_environment #-}

instance Method "set_environment" GodotCamera
           (GodotEnvironment -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_environment (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_environment
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_environment #-}

instance Method "get_environment" GodotCamera (IO GodotEnvironment)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_environment (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_keep_aspect_mode
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_keep_aspect_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_keep_aspect_mode #-}

instance Method "set_keep_aspect_mode" GodotCamera (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_keep_aspect_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_keep_aspect_mode
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_keep_aspect_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_keep_aspect_mode #-}

instance Method "get_keep_aspect_mode" GodotCamera (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_keep_aspect_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_doppler_tracking
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_doppler_tracking" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_doppler_tracking #-}

instance Method "set_doppler_tracking" GodotCamera (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_doppler_tracking (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_doppler_tracking
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_doppler_tracking" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_doppler_tracking #-}

instance Method "get_doppler_tracking" GodotCamera (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_doppler_tracking (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_set_cull_mask_bit
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "set_cull_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_set_cull_mask_bit #-}

instance Method "set_cull_mask_bit" GodotCamera
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_set_cull_mask_bit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera_get_cull_mask_bit
  = unsafePerformIO $
      withCString "Camera" $
        \ clsNamePtr ->
          withCString "get_cull_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera_get_cull_mask_bit #-}

instance Method "get_cull_mask_bit" GodotCamera (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera_get_cull_mask_bit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEnvironment = GodotEnvironment GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotEnvironment where
        type BaseClass GodotEnvironment = GodotResource
        super = coerce
bindEnvironment_set_background
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_background" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_background #-}

instance Method "set_background" GodotEnvironment (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_background (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_sky
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_sky" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_sky #-}

instance Method "set_sky" GodotEnvironment (GodotSky -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_sky (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_sky_custom_fov
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_sky_custom_fov" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_sky_custom_fov #-}

instance Method "set_sky_custom_fov" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_sky_custom_fov
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_bg_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_bg_color #-}

instance Method "set_bg_color" GodotEnvironment
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_bg_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_bg_energy
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_bg_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_bg_energy #-}

instance Method "set_bg_energy" GodotEnvironment (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_bg_energy (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_canvas_max_layer
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_canvas_max_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_canvas_max_layer #-}

instance Method "set_canvas_max_layer" GodotEnvironment
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_canvas_max_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ambient_light_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ambient_light_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ambient_light_color #-}

instance Method "set_ambient_light_color" GodotEnvironment
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ambient_light_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ambient_light_energy
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ambient_light_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ambient_light_energy #-}

instance Method "set_ambient_light_energy" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ambient_light_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ambient_light_sky_contribution
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ambient_light_sky_contribution" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ambient_light_sky_contribution #-}

instance Method "set_ambient_light_sky_contribution"
           GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_set_ambient_light_sky_contribution
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_background
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_background" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_background #-}

instance Method "get_background" GodotEnvironment (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_background (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_sky
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_sky" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_sky #-}

instance Method "get_sky" GodotEnvironment (IO GodotSky) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_sky (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_sky_custom_fov
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_sky_custom_fov" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_sky_custom_fov #-}

instance Method "get_sky_custom_fov" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_sky_custom_fov
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_bg_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_bg_color #-}

instance Method "get_bg_color" GodotEnvironment (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_bg_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_bg_energy
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_bg_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_bg_energy #-}

instance Method "get_bg_energy" GodotEnvironment (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_bg_energy (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_canvas_max_layer
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_canvas_max_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_canvas_max_layer #-}

instance Method "get_canvas_max_layer" GodotEnvironment (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_canvas_max_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ambient_light_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ambient_light_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ambient_light_color #-}

instance Method "get_ambient_light_color" GodotEnvironment
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ambient_light_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ambient_light_energy
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ambient_light_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ambient_light_energy #-}

instance Method "get_ambient_light_energy" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ambient_light_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ambient_light_sky_contribution
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ambient_light_sky_contribution" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ambient_light_sky_contribution #-}

instance Method "get_ambient_light_sky_contribution"
           GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_get_ambient_light_sky_contribution
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_enabled #-}

instance Method "set_fog_enabled" GodotEnvironment (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_fog_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_fog_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_fog_enabled #-}

instance Method "is_fog_enabled" GodotEnvironment (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_fog_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_color #-}

instance Method "set_fog_color" GodotEnvironment
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_color #-}

instance Method "get_fog_color" GodotEnvironment (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_sun_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_sun_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_sun_color #-}

instance Method "set_fog_sun_color" GodotEnvironment
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_sun_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_sun_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_sun_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_sun_color #-}

instance Method "get_fog_sun_color" GodotEnvironment
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_sun_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_sun_amount
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_sun_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_sun_amount #-}

instance Method "set_fog_sun_amount" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_sun_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_sun_amount
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_sun_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_sun_amount #-}

instance Method "get_fog_sun_amount" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_sun_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_depth_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_depth_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_depth_enabled #-}

instance Method "set_fog_depth_enabled" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_depth_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_fog_depth_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_fog_depth_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_fog_depth_enabled #-}

instance Method "is_fog_depth_enabled" GodotEnvironment (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_fog_depth_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_depth_begin
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_depth_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_depth_begin #-}

instance Method "set_fog_depth_begin" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_depth_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_depth_begin
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_depth_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_depth_begin #-}

instance Method "get_fog_depth_begin" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_depth_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_depth_curve
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_depth_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_depth_curve #-}

instance Method "set_fog_depth_curve" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_depth_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_depth_curve
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_depth_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_depth_curve #-}

instance Method "get_fog_depth_curve" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_depth_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_transmit_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_transmit_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_transmit_enabled #-}

instance Method "set_fog_transmit_enabled" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_transmit_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_fog_transmit_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_fog_transmit_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_fog_transmit_enabled #-}

instance Method "is_fog_transmit_enabled" GodotEnvironment
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_fog_transmit_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_transmit_curve
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_transmit_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_transmit_curve #-}

instance Method "set_fog_transmit_curve" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_transmit_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_transmit_curve
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_transmit_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_transmit_curve #-}

instance Method "get_fog_transmit_curve" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_transmit_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_height_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_height_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_height_enabled #-}

instance Method "set_fog_height_enabled" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_height_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_fog_height_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_fog_height_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_fog_height_enabled #-}

instance Method "is_fog_height_enabled" GodotEnvironment (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_fog_height_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_height_min
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_height_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_height_min #-}

instance Method "set_fog_height_min" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_height_min
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_height_min
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_height_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_height_min #-}

instance Method "get_fog_height_min" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_height_min
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_height_max
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_height_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_height_max #-}

instance Method "set_fog_height_max" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_height_max
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_height_max
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_height_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_height_max #-}

instance Method "get_fog_height_max" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_height_max
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_fog_height_curve
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_fog_height_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_fog_height_curve #-}

instance Method "set_fog_height_curve" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_fog_height_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_fog_height_curve
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_fog_height_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_fog_height_curve #-}

instance Method "get_fog_height_curve" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_fog_height_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemapper
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemapper" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemapper #-}

instance Method "set_tonemapper" GodotEnvironment (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_tonemapper (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemapper
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemapper" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemapper #-}

instance Method "get_tonemapper" GodotEnvironment (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_tonemapper (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemap_exposure
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemap_exposure" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemap_exposure #-}

instance Method "set_tonemap_exposure" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_tonemap_exposure
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemap_exposure
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemap_exposure" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemap_exposure #-}

instance Method "get_tonemap_exposure" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_tonemap_exposure
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemap_white
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemap_white" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemap_white #-}

instance Method "set_tonemap_white" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_tonemap_white
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemap_white
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemap_white" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemap_white #-}

instance Method "get_tonemap_white" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_tonemap_white
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemap_auto_exposure
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemap_auto_exposure" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemap_auto_exposure #-}

instance Method "set_tonemap_auto_exposure" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_tonemap_auto_exposure
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemap_auto_exposure
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemap_auto_exposure" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemap_auto_exposure #-}

instance Method "get_tonemap_auto_exposure" GodotEnvironment
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_tonemap_auto_exposure
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemap_auto_exposure_max
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemap_auto_exposure_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemap_auto_exposure_max #-}

instance Method "set_tonemap_auto_exposure_max" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_set_tonemap_auto_exposure_max
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemap_auto_exposure_max
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemap_auto_exposure_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemap_auto_exposure_max #-}

instance Method "get_tonemap_auto_exposure_max" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_get_tonemap_auto_exposure_max
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemap_auto_exposure_min
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemap_auto_exposure_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemap_auto_exposure_min #-}

instance Method "set_tonemap_auto_exposure_min" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_set_tonemap_auto_exposure_min
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemap_auto_exposure_min
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemap_auto_exposure_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemap_auto_exposure_min #-}

instance Method "get_tonemap_auto_exposure_min" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_get_tonemap_auto_exposure_min
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemap_auto_exposure_speed
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemap_auto_exposure_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemap_auto_exposure_speed #-}

instance Method "set_tonemap_auto_exposure_speed" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_set_tonemap_auto_exposure_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemap_auto_exposure_speed
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemap_auto_exposure_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemap_auto_exposure_speed #-}

instance Method "get_tonemap_auto_exposure_speed" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_get_tonemap_auto_exposure_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_tonemap_auto_exposure_grey
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_tonemap_auto_exposure_grey" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_tonemap_auto_exposure_grey #-}

instance Method "set_tonemap_auto_exposure_grey" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_set_tonemap_auto_exposure_grey
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_tonemap_auto_exposure_grey
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_tonemap_auto_exposure_grey" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_tonemap_auto_exposure_grey #-}

instance Method "get_tonemap_auto_exposure_grey" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_get_tonemap_auto_exposure_grey
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssr_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssr_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssr_enabled #-}

instance Method "set_ssr_enabled" GodotEnvironment (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssr_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_ssr_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_ssr_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_ssr_enabled #-}

instance Method "is_ssr_enabled" GodotEnvironment (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_ssr_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssr_max_steps
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssr_max_steps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssr_max_steps #-}

instance Method "set_ssr_max_steps" GodotEnvironment (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssr_max_steps
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssr_max_steps
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssr_max_steps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssr_max_steps #-}

instance Method "get_ssr_max_steps" GodotEnvironment (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssr_max_steps
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssr_fade_in
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssr_fade_in" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssr_fade_in #-}

instance Method "set_ssr_fade_in" GodotEnvironment (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssr_fade_in (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssr_fade_in
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssr_fade_in" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssr_fade_in #-}

instance Method "get_ssr_fade_in" GodotEnvironment (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssr_fade_in (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssr_fade_out
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssr_fade_out" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssr_fade_out #-}

instance Method "set_ssr_fade_out" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssr_fade_out
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssr_fade_out
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssr_fade_out" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssr_fade_out #-}

instance Method "get_ssr_fade_out" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssr_fade_out
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssr_depth_tolerance
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssr_depth_tolerance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssr_depth_tolerance #-}

instance Method "set_ssr_depth_tolerance" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssr_depth_tolerance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssr_depth_tolerance
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssr_depth_tolerance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssr_depth_tolerance #-}

instance Method "get_ssr_depth_tolerance" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssr_depth_tolerance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssr_rough
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssr_rough" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssr_rough #-}

instance Method "set_ssr_rough" GodotEnvironment (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssr_rough (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_ssr_rough
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_ssr_rough" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_ssr_rough #-}

instance Method "is_ssr_rough" GodotEnvironment (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_ssr_rough (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_enabled #-}

instance Method "set_ssao_enabled" GodotEnvironment (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_ssao_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_ssao_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_ssao_enabled #-}

instance Method "is_ssao_enabled" GodotEnvironment (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_ssao_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_radius
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_radius #-}

instance Method "set_ssao_radius" GodotEnvironment (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_radius
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_radius #-}

instance Method "get_ssao_radius" GodotEnvironment (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_intensity
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_intensity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_intensity #-}

instance Method "set_ssao_intensity" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_intensity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_intensity
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_intensity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_intensity #-}

instance Method "get_ssao_intensity" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_intensity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_radius2
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_radius2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_radius2 #-}

instance Method "set_ssao_radius2" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_radius2
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_radius2
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_radius2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_radius2 #-}

instance Method "get_ssao_radius2" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_radius2
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_intensity2
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_intensity2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_intensity2 #-}

instance Method "set_ssao_intensity2" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_intensity2
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_intensity2
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_intensity2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_intensity2 #-}

instance Method "get_ssao_intensity2" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_intensity2
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_bias
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_bias #-}

instance Method "set_ssao_bias" GodotEnvironment (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_bias (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_bias
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_bias #-}

instance Method "get_ssao_bias" GodotEnvironment (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_bias (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_direct_light_affect
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_direct_light_affect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_direct_light_affect #-}

instance Method "set_ssao_direct_light_affect" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_direct_light_affect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_direct_light_affect
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_direct_light_affect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_direct_light_affect #-}

instance Method "get_ssao_direct_light_affect" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_direct_light_affect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_ao_channel_affect
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_ao_channel_affect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_ao_channel_affect #-}

instance Method "set_ssao_ao_channel_affect" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_ao_channel_affect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_ao_channel_affect
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_ao_channel_affect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_ao_channel_affect #-}

instance Method "get_ssao_ao_channel_affect" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_ao_channel_affect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_color #-}

instance Method "set_ssao_color" GodotEnvironment
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_color
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_color #-}

instance Method "get_ssao_color" GodotEnvironment (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_blur
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_blur" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_blur #-}

instance Method "set_ssao_blur" GodotEnvironment (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_blur (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_blur
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_blur" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_blur #-}

instance Method "get_ssao_blur" GodotEnvironment (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_blur (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_quality
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_quality #-}

instance Method "set_ssao_quality" GodotEnvironment (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_quality
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_quality #-}

instance Method "get_ssao_quality" GodotEnvironment (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_ssao_edge_sharpness
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_ssao_edge_sharpness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_ssao_edge_sharpness #-}

instance Method "set_ssao_edge_sharpness" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_ssao_edge_sharpness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_ssao_edge_sharpness
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_ssao_edge_sharpness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_ssao_edge_sharpness #-}

instance Method "get_ssao_edge_sharpness" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_ssao_edge_sharpness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_far_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_far_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_far_enabled #-}

instance Method "set_dof_blur_far_enabled" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_far_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_dof_blur_far_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_dof_blur_far_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_dof_blur_far_enabled #-}

instance Method "is_dof_blur_far_enabled" GodotEnvironment
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_dof_blur_far_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_far_distance
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_far_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_far_distance #-}

instance Method "set_dof_blur_far_distance" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_far_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_far_distance
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_far_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_far_distance #-}

instance Method "get_dof_blur_far_distance" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_far_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_far_transition
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_far_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_far_transition #-}

instance Method "set_dof_blur_far_transition" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_far_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_far_transition
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_far_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_far_transition #-}

instance Method "get_dof_blur_far_transition" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_far_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_far_amount
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_far_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_far_amount #-}

instance Method "set_dof_blur_far_amount" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_far_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_far_amount
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_far_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_far_amount #-}

instance Method "get_dof_blur_far_amount" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_far_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_far_quality
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_far_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_far_quality #-}

instance Method "set_dof_blur_far_quality" GodotEnvironment
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_far_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_far_quality
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_far_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_far_quality #-}

instance Method "get_dof_blur_far_quality" GodotEnvironment
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_far_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_near_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_near_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_near_enabled #-}

instance Method "set_dof_blur_near_enabled" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_near_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_dof_blur_near_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_dof_blur_near_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_dof_blur_near_enabled #-}

instance Method "is_dof_blur_near_enabled" GodotEnvironment
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_dof_blur_near_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_near_distance
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_near_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_near_distance #-}

instance Method "set_dof_blur_near_distance" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_near_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_near_distance
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_near_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_near_distance #-}

instance Method "get_dof_blur_near_distance" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_near_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_near_transition
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_near_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_near_transition #-}

instance Method "set_dof_blur_near_transition" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_near_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_near_transition
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_near_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_near_transition #-}

instance Method "get_dof_blur_near_transition" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_near_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_near_amount
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_near_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_near_amount #-}

instance Method "set_dof_blur_near_amount" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_near_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_near_amount
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_near_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_near_amount #-}

instance Method "get_dof_blur_near_amount" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_near_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_dof_blur_near_quality
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_dof_blur_near_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_dof_blur_near_quality #-}

instance Method "set_dof_blur_near_quality" GodotEnvironment
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_dof_blur_near_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_dof_blur_near_quality
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_dof_blur_near_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_dof_blur_near_quality #-}

instance Method "get_dof_blur_near_quality" GodotEnvironment
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_dof_blur_near_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_enabled #-}

instance Method "set_glow_enabled" GodotEnvironment (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_glow_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_glow_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_glow_enabled #-}

instance Method "is_glow_enabled" GodotEnvironment (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_glow_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_level
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_level" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_level #-}

instance Method "set_glow_level" GodotEnvironment
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_level (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_glow_level_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_glow_level_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_glow_level_enabled #-}

instance Method "is_glow_level_enabled" GodotEnvironment
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_glow_level_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_intensity
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_intensity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_intensity #-}

instance Method "set_glow_intensity" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_intensity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_glow_intensity
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_glow_intensity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_glow_intensity #-}

instance Method "get_glow_intensity" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_glow_intensity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_strength
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_strength" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_strength #-}

instance Method "set_glow_strength" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_strength
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_glow_strength
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_glow_strength" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_glow_strength #-}

instance Method "get_glow_strength" GodotEnvironment (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_glow_strength
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_bloom
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_bloom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_bloom #-}

instance Method "set_glow_bloom" GodotEnvironment (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_bloom (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_glow_bloom
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_glow_bloom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_glow_bloom #-}

instance Method "get_glow_bloom" GodotEnvironment (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_glow_bloom (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_blend_mode
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_blend_mode #-}

instance Method "set_glow_blend_mode" GodotEnvironment
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_glow_blend_mode
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_glow_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_glow_blend_mode #-}

instance Method "get_glow_blend_mode" GodotEnvironment (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_glow_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_hdr_bleed_threshold
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_hdr_bleed_threshold" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_hdr_bleed_threshold #-}

instance Method "set_glow_hdr_bleed_threshold" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_hdr_bleed_threshold
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_glow_hdr_bleed_threshold
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_glow_hdr_bleed_threshold" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_glow_hdr_bleed_threshold #-}

instance Method "get_glow_hdr_bleed_threshold" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_glow_hdr_bleed_threshold
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_hdr_bleed_scale
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_hdr_bleed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_hdr_bleed_scale #-}

instance Method "set_glow_hdr_bleed_scale" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_hdr_bleed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_glow_hdr_bleed_scale
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_glow_hdr_bleed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_glow_hdr_bleed_scale #-}

instance Method "get_glow_hdr_bleed_scale" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_glow_hdr_bleed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_glow_bicubic_upscale
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_glow_bicubic_upscale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_glow_bicubic_upscale #-}

instance Method "set_glow_bicubic_upscale" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_glow_bicubic_upscale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_glow_bicubic_upscale_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_glow_bicubic_upscale_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_glow_bicubic_upscale_enabled #-}

instance Method "is_glow_bicubic_upscale_enabled" GodotEnvironment
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_is_glow_bicubic_upscale_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_adjustment_enable
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_adjustment_enable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_adjustment_enable #-}

instance Method "set_adjustment_enable" GodotEnvironment
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_adjustment_enable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_is_adjustment_enabled
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "is_adjustment_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_is_adjustment_enabled #-}

instance Method "is_adjustment_enabled" GodotEnvironment (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_is_adjustment_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_adjustment_brightness
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_adjustment_brightness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_adjustment_brightness #-}

instance Method "set_adjustment_brightness" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_adjustment_brightness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_adjustment_brightness
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_adjustment_brightness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_adjustment_brightness #-}

instance Method "get_adjustment_brightness" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_adjustment_brightness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_adjustment_contrast
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_adjustment_contrast" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_adjustment_contrast #-}

instance Method "set_adjustment_contrast" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_adjustment_contrast
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_adjustment_contrast
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_adjustment_contrast" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_adjustment_contrast #-}

instance Method "get_adjustment_contrast" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_adjustment_contrast
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_adjustment_saturation
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_adjustment_saturation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_adjustment_saturation #-}

instance Method "set_adjustment_saturation" GodotEnvironment
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_set_adjustment_saturation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_adjustment_saturation
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_adjustment_saturation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_adjustment_saturation #-}

instance Method "get_adjustment_saturation" GodotEnvironment
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEnvironment_get_adjustment_saturation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_set_adjustment_color_correction
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "set_adjustment_color_correction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_set_adjustment_color_correction #-}

instance Method "set_adjustment_color_correction" GodotEnvironment
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_set_adjustment_color_correction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEnvironment_get_adjustment_color_correction
  = unsafePerformIO $
      withCString "Environment" $
        \ clsNamePtr ->
          withCString "get_adjustment_color_correction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEnvironment_get_adjustment_color_correction #-}

instance Method "get_adjustment_color_correction" GodotEnvironment
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEnvironment_get_adjustment_color_correction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotClippedCamera = GodotClippedCamera GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotClippedCamera where
        type BaseClass GodotClippedCamera = GodotCamera
        super = coerce
bindClippedCamera_set_margin
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "set_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_set_margin #-}

instance Method "set_margin" GodotClippedCamera (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_set_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_get_margin
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_get_margin #-}

instance Method "get_margin" GodotClippedCamera (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_get_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_set_process_mode
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "set_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_set_process_mode #-}

instance Method "set_process_mode" GodotClippedCamera
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_set_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_get_process_mode
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "get_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_get_process_mode #-}

instance Method "get_process_mode" GodotClippedCamera (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_get_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_set_collision_mask
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_set_collision_mask #-}

instance Method "set_collision_mask" GodotClippedCamera
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_get_collision_mask
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_get_collision_mask #-}

instance Method "get_collision_mask" GodotClippedCamera (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_set_collision_mask_bit
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotClippedCamera
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_get_collision_mask_bit
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotClippedCamera
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_add_exception_rid
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "add_exception_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_add_exception_rid #-}

instance Method "add_exception_rid" GodotClippedCamera
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_add_exception_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_add_exception
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "add_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_add_exception #-}

instance Method "add_exception" GodotClippedCamera
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_add_exception (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_remove_exception_rid
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "remove_exception_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_remove_exception_rid #-}

instance Method "remove_exception_rid" GodotClippedCamera
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_remove_exception_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_remove_exception
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "remove_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_remove_exception #-}

instance Method "remove_exception" GodotClippedCamera
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_remove_exception
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_set_clip_to_areas
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "set_clip_to_areas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_set_clip_to_areas #-}

instance Method "set_clip_to_areas" GodotClippedCamera
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_set_clip_to_areas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_is_clip_to_areas_enabled
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "is_clip_to_areas_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_is_clip_to_areas_enabled #-}

instance Method "is_clip_to_areas_enabled" GodotClippedCamera
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_is_clip_to_areas_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_set_clip_to_bodies
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "set_clip_to_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_set_clip_to_bodies #-}

instance Method "set_clip_to_bodies" GodotClippedCamera
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_set_clip_to_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_is_clip_to_bodies_enabled
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "is_clip_to_bodies_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_is_clip_to_bodies_enabled #-}

instance Method "is_clip_to_bodies_enabled" GodotClippedCamera
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_is_clip_to_bodies_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindClippedCamera_clear_exceptions
  = unsafePerformIO $
      withCString "ClippedCamera" $
        \ clsNamePtr ->
          withCString "clear_exceptions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindClippedCamera_clear_exceptions #-}

instance Method "clear_exceptions" GodotClippedCamera (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindClippedCamera_clear_exceptions
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotListener = GodotListener GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotListener where
        type BaseClass GodotListener = GodotSpatial
        super = coerce
bindListener_make_current
  = unsafePerformIO $
      withCString "Listener" $
        \ clsNamePtr ->
          withCString "make_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindListener_make_current #-}

instance Method "make_current" GodotListener (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindListener_make_current (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindListener_clear_current
  = unsafePerformIO $
      withCString "Listener" $
        \ clsNamePtr ->
          withCString "clear_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindListener_clear_current #-}

instance Method "clear_current" GodotListener (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindListener_clear_current (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindListener_is_current
  = unsafePerformIO $
      withCString "Listener" $
        \ clsNamePtr ->
          withCString "is_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindListener_is_current #-}

instance Method "is_current" GodotListener (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindListener_is_current (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindListener_get_listener_transform
  = unsafePerformIO $
      withCString "Listener" $
        \ clsNamePtr ->
          withCString "get_listener_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindListener_get_listener_transform #-}

instance Method "get_listener_transform" GodotListener
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindListener_get_listener_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotARVRCamera = GodotARVRCamera GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotARVRCamera where
        type BaseClass GodotARVRCamera = GodotCamera
        super = coerce

newtype GodotARVRController = GodotARVRController GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotARVRController where
        type BaseClass GodotARVRController = GodotSpatial
        super = coerce
bindARVRController_set_controller_id
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "set_controller_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_set_controller_id #-}

instance Method "set_controller_id" GodotARVRController
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_set_controller_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_get_controller_id
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "get_controller_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_get_controller_id #-}

instance Method "get_controller_id" GodotARVRController (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_get_controller_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_get_controller_name
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "get_controller_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_get_controller_name #-}

instance Method "get_controller_name" GodotARVRController
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_get_controller_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_get_joystick_id
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "get_joystick_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_get_joystick_id #-}

instance Method "get_joystick_id" GodotARVRController (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_get_joystick_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_is_button_pressed
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "is_button_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_is_button_pressed #-}

instance Method "is_button_pressed" GodotARVRController
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_is_button_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_get_joystick_axis
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "get_joystick_axis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_get_joystick_axis #-}

instance Method "get_joystick_axis" GodotARVRController
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_get_joystick_axis
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_get_is_active
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "get_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_get_is_active #-}

instance Method "get_is_active" GodotARVRController (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_get_is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_get_hand
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "get_hand" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_get_hand #-}

instance Method "get_hand" GodotARVRController (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_get_hand (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_get_rumble
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "get_rumble" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_get_rumble #-}

instance Method "get_rumble" GodotARVRController (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_get_rumble (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRController_set_rumble
  = unsafePerformIO $
      withCString "ARVRController" $
        \ clsNamePtr ->
          withCString "set_rumble" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRController_set_rumble #-}

instance Method "set_rumble" GodotARVRController (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRController_set_rumble (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotARVRAnchor = GodotARVRAnchor GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotARVRAnchor where
        type BaseClass GodotARVRAnchor = GodotSpatial
        super = coerce
bindARVRAnchor_set_anchor_id
  = unsafePerformIO $
      withCString "ARVRAnchor" $
        \ clsNamePtr ->
          withCString "set_anchor_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRAnchor_set_anchor_id #-}

instance Method "set_anchor_id" GodotARVRAnchor (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRAnchor_set_anchor_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRAnchor_get_anchor_id
  = unsafePerformIO $
      withCString "ARVRAnchor" $
        \ clsNamePtr ->
          withCString "get_anchor_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRAnchor_get_anchor_id #-}

instance Method "get_anchor_id" GodotARVRAnchor (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRAnchor_get_anchor_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRAnchor_get_anchor_name
  = unsafePerformIO $
      withCString "ARVRAnchor" $
        \ clsNamePtr ->
          withCString "get_anchor_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRAnchor_get_anchor_name #-}

instance Method "get_anchor_name" GodotARVRAnchor (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRAnchor_get_anchor_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRAnchor_get_is_active
  = unsafePerformIO $
      withCString "ARVRAnchor" $
        \ clsNamePtr ->
          withCString "get_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRAnchor_get_is_active #-}

instance Method "get_is_active" GodotARVRAnchor (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRAnchor_get_is_active (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRAnchor_get_size
  = unsafePerformIO $
      withCString "ARVRAnchor" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRAnchor_get_size #-}

instance Method "get_size" GodotARVRAnchor (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRAnchor_get_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVRAnchor_get_plane
  = unsafePerformIO $
      withCString "ARVRAnchor" $
        \ clsNamePtr ->
          withCString "get_plane" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVRAnchor_get_plane #-}

instance Method "get_plane" GodotARVRAnchor (IO GodotPlane) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVRAnchor_get_plane (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotARVROrigin = GodotARVROrigin GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotARVROrigin where
        type BaseClass GodotARVROrigin = GodotSpatial
        super = coerce
bindARVROrigin_set_world_scale
  = unsafePerformIO $
      withCString "ARVROrigin" $
        \ clsNamePtr ->
          withCString "set_world_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVROrigin_set_world_scale #-}

instance Method "set_world_scale" GodotARVROrigin (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVROrigin_set_world_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindARVROrigin_get_world_scale
  = unsafePerformIO $
      withCString "ARVROrigin" $
        \ clsNamePtr ->
          withCString "get_world_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindARVROrigin_get_world_scale #-}

instance Method "get_world_scale" GodotARVROrigin (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindARVROrigin_get_world_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotInterpolatedCamera = GodotInterpolatedCamera GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotInterpolatedCamera where
        type BaseClass GodotInterpolatedCamera = GodotCamera
        super = coerce
bindInterpolatedCamera_set_target_path
  = unsafePerformIO $
      withCString "InterpolatedCamera" $
        \ clsNamePtr ->
          withCString "set_target_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInterpolatedCamera_set_target_path #-}

instance Method "set_target_path" GodotInterpolatedCamera
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInterpolatedCamera_set_target_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInterpolatedCamera_get_target_path
  = unsafePerformIO $
      withCString "InterpolatedCamera" $
        \ clsNamePtr ->
          withCString "get_target_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInterpolatedCamera_get_target_path #-}

instance Method "get_target_path" GodotInterpolatedCamera
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInterpolatedCamera_get_target_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInterpolatedCamera_set_target
  = unsafePerformIO $
      withCString "InterpolatedCamera" $
        \ clsNamePtr ->
          withCString "set_target" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInterpolatedCamera_set_target #-}

instance Method "set_target" GodotInterpolatedCamera
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInterpolatedCamera_set_target
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInterpolatedCamera_set_speed
  = unsafePerformIO $
      withCString "InterpolatedCamera" $
        \ clsNamePtr ->
          withCString "set_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInterpolatedCamera_set_speed #-}

instance Method "set_speed" GodotInterpolatedCamera
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInterpolatedCamera_set_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInterpolatedCamera_get_speed
  = unsafePerformIO $
      withCString "InterpolatedCamera" $
        \ clsNamePtr ->
          withCString "get_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInterpolatedCamera_get_speed #-}

instance Method "get_speed" GodotInterpolatedCamera (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindInterpolatedCamera_get_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInterpolatedCamera_set_interpolation_enabled
  = unsafePerformIO $
      withCString "InterpolatedCamera" $
        \ clsNamePtr ->
          withCString "set_interpolation_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInterpolatedCamera_set_interpolation_enabled #-}

instance Method "set_interpolation_enabled" GodotInterpolatedCamera
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindInterpolatedCamera_set_interpolation_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindInterpolatedCamera_is_interpolation_enabled
  = unsafePerformIO $
      withCString "InterpolatedCamera" $
        \ clsNamePtr ->
          withCString "is_interpolation_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindInterpolatedCamera_is_interpolation_enabled #-}

instance Method "is_interpolation_enabled" GodotInterpolatedCamera
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindInterpolatedCamera_is_interpolation_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMeshInstance = GodotMeshInstance GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotMeshInstance where
        type BaseClass GodotMeshInstance = GodotGeometryInstance
        super = coerce
bindMeshInstance_set_mesh
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "set_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_set_mesh #-}

instance Method "set_mesh" GodotMeshInstance (GodotMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_set_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_get_mesh
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "get_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_get_mesh #-}

instance Method "get_mesh" GodotMeshInstance (IO GodotMesh) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_get_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_set_skeleton_path
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "set_skeleton_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_set_skeleton_path #-}

instance Method "set_skeleton_path" GodotMeshInstance
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_set_skeleton_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_get_skeleton_path
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "get_skeleton_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_get_skeleton_path #-}

instance Method "get_skeleton_path" GodotMeshInstance
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_get_skeleton_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_get_surface_material_count
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "get_surface_material_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_get_surface_material_count #-}

instance Method "get_surface_material_count" GodotMeshInstance
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_get_surface_material_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_set_surface_material
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "set_surface_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_set_surface_material #-}

instance Method "set_surface_material" GodotMeshInstance
           (Int -> GodotMaterial -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_set_surface_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_get_surface_material
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "get_surface_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_get_surface_material #-}

instance Method "get_surface_material" GodotMeshInstance
           (Int -> IO GodotMaterial)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_get_surface_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_create_trimesh_collision
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "create_trimesh_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_create_trimesh_collision #-}

instance Method "create_trimesh_collision" GodotMeshInstance
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_create_trimesh_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_create_convex_collision
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "create_convex_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_create_convex_collision #-}

instance Method "create_convex_collision" GodotMeshInstance (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_create_convex_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance__mesh_changed
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "_mesh_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance__mesh_changed #-}

instance Method "_mesh_changed" GodotMeshInstance (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance__mesh_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance_create_debug_tangents
  = unsafePerformIO $
      withCString "MeshInstance" $
        \ clsNamePtr ->
          withCString "create_debug_tangents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance_create_debug_tangents #-}

instance Method "create_debug_tangents" GodotMeshInstance (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance_create_debug_tangents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMesh = GodotMesh GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotMesh where
        type BaseClass GodotMesh = GodotResource
        super = coerce
bindMesh_set_lightmap_size_hint
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "set_lightmap_size_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_set_lightmap_size_hint #-}

instance Method "set_lightmap_size_hint" GodotMesh
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_set_lightmap_size_hint (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_get_lightmap_size_hint
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "get_lightmap_size_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_get_lightmap_size_hint #-}

instance Method "get_lightmap_size_hint" GodotMesh
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_get_lightmap_size_hint (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_get_surface_count
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "get_surface_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_get_surface_count #-}

instance Method "get_surface_count" GodotMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_get_surface_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_surface_get_arrays
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "surface_get_arrays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_surface_get_arrays #-}

instance Method "surface_get_arrays" GodotMesh
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_surface_get_arrays (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_surface_get_blend_shape_arrays
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "surface_get_blend_shape_arrays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_surface_get_blend_shape_arrays #-}

instance Method "surface_get_blend_shape_arrays" GodotMesh
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_surface_get_blend_shape_arrays
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_surface_get_material
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "surface_get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_surface_get_material #-}

instance Method "surface_get_material" GodotMesh
           (Int -> IO GodotMaterial)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_surface_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_create_trimesh_shape
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "create_trimesh_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_create_trimesh_shape #-}

instance Method "create_trimesh_shape" GodotMesh (IO GodotShape)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_create_trimesh_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_create_convex_shape
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "create_convex_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_create_convex_shape #-}

instance Method "create_convex_shape" GodotMesh (IO GodotShape)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_create_convex_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_create_outline
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "create_outline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_create_outline #-}

instance Method "create_outline" GodotMesh (Float -> IO GodotMesh)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_create_outline (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_get_faces
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "get_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_get_faces #-}

instance Method "get_faces" GodotMesh (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_get_faces (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMesh_generate_triangle_mesh
  = unsafePerformIO $
      withCString "Mesh" $
        \ clsNamePtr ->
          withCString "generate_triangle_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMesh_generate_triangle_mesh #-}

instance Method "generate_triangle_mesh" GodotMesh
           (IO GodotTriangleMesh)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMesh_generate_triangle_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotImmediateGeometry = GodotImmediateGeometry GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotImmediateGeometry where
        type BaseClass GodotImmediateGeometry = GodotGeometryInstance
        super = coerce
bindImmediateGeometry_begin
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_begin #-}

instance Method "begin" GodotImmediateGeometry
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_begin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_set_normal
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "set_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_set_normal #-}

instance Method "set_normal" GodotImmediateGeometry
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_set_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_set_tangent
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "set_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_set_tangent #-}

instance Method "set_tangent" GodotImmediateGeometry
           (GodotPlane -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_set_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_set_color
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_set_color #-}

instance Method "set_color" GodotImmediateGeometry
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_set_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_set_uv
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "set_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_set_uv #-}

instance Method "set_uv" GodotImmediateGeometry
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_set_uv (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_set_uv2
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "set_uv2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_set_uv2 #-}

instance Method "set_uv2" GodotImmediateGeometry
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_set_uv2 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_add_vertex
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "add_vertex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_add_vertex #-}

instance Method "add_vertex" GodotImmediateGeometry
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_add_vertex
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_add_sphere
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "add_sphere" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_add_sphere #-}

instance Method "add_sphere" GodotImmediateGeometry
           (Int -> Int -> Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_add_sphere
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_end
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_end #-}

instance Method "end" GodotImmediateGeometry (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_end (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImmediateGeometry_clear
  = unsafePerformIO $
      withCString "ImmediateGeometry" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImmediateGeometry_clear #-}

instance Method "clear" GodotImmediateGeometry (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImmediateGeometry_clear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpriteBase3D = GodotSpriteBase3D GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotSpriteBase3D where
        type BaseClass GodotSpriteBase3D = GodotGeometryInstance
        super = coerce
bindSpriteBase3D_set_centered
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_centered #-}

instance Method "set_centered" GodotSpriteBase3D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_centered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_is_centered
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "is_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_is_centered #-}

instance Method "is_centered" GodotSpriteBase3D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_is_centered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_offset
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_offset #-}

instance Method "set_offset" GodotSpriteBase3D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_offset
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_offset #-}

instance Method "get_offset" GodotSpriteBase3D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_flip_h
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_flip_h" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_flip_h #-}

instance Method "set_flip_h" GodotSpriteBase3D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_flip_h (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_is_flipped_h
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "is_flipped_h" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_is_flipped_h #-}

instance Method "is_flipped_h" GodotSpriteBase3D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_is_flipped_h (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_flip_v
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_flip_v" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_flip_v #-}

instance Method "set_flip_v" GodotSpriteBase3D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_flip_v (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_is_flipped_v
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "is_flipped_v" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_is_flipped_v #-}

instance Method "is_flipped_v" GodotSpriteBase3D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_is_flipped_v (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_modulate
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_modulate #-}

instance Method "set_modulate" GodotSpriteBase3D
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_modulate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_modulate
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_modulate #-}

instance Method "get_modulate" GodotSpriteBase3D (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_modulate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_opacity
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_opacity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_opacity #-}

instance Method "set_opacity" GodotSpriteBase3D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_opacity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_opacity
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_opacity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_opacity #-}

instance Method "get_opacity" GodotSpriteBase3D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_opacity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_pixel_size
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_pixel_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_pixel_size #-}

instance Method "set_pixel_size" GodotSpriteBase3D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_pixel_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_pixel_size
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_pixel_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_pixel_size #-}

instance Method "get_pixel_size" GodotSpriteBase3D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_pixel_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_axis
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_axis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_axis #-}

instance Method "set_axis" GodotSpriteBase3D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_axis (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_axis
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_axis" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_axis #-}

instance Method "get_axis" GodotSpriteBase3D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_axis (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_draw_flag
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_draw_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_draw_flag #-}

instance Method "set_draw_flag" GodotSpriteBase3D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_draw_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_draw_flag
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_draw_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_draw_flag #-}

instance Method "get_draw_flag" GodotSpriteBase3D (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_draw_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_set_alpha_cut_mode
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "set_alpha_cut_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_set_alpha_cut_mode #-}

instance Method "set_alpha_cut_mode" GodotSpriteBase3D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_set_alpha_cut_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_alpha_cut_mode
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_alpha_cut_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_alpha_cut_mode #-}

instance Method "get_alpha_cut_mode" GodotSpriteBase3D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_alpha_cut_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_get_item_rect
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "get_item_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_get_item_rect #-}

instance Method "get_item_rect" GodotSpriteBase3D (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_get_item_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D_generate_triangle_mesh
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "generate_triangle_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D_generate_triangle_mesh #-}

instance Method "generate_triangle_mesh" GodotSpriteBase3D
           (IO GodotTriangleMesh)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D_generate_triangle_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D__queue_update
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "_queue_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D__queue_update #-}

instance Method "_queue_update" GodotSpriteBase3D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D__queue_update (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteBase3D__im_update
  = unsafePerformIO $
      withCString "SpriteBase3D" $
        \ clsNamePtr ->
          withCString "_im_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteBase3D__im_update #-}

instance Method "_im_update" GodotSpriteBase3D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteBase3D__im_update (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSprite3D = GodotSprite3D GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotSprite3D where
        type BaseClass GodotSprite3D = GodotSpriteBase3D
        super = coerce
bindSprite3D_set_texture
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_set_texture #-}

instance Method "set_texture" GodotSprite3D (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_set_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_get_texture
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_get_texture #-}

instance Method "get_texture" GodotSprite3D (IO GodotTexture) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_get_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_set_region
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "set_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_set_region #-}

instance Method "set_region" GodotSprite3D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_set_region (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_is_region
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "is_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_is_region #-}

instance Method "is_region" GodotSprite3D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_is_region (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_set_region_rect
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "set_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_set_region_rect #-}

instance Method "set_region_rect" GodotSprite3D
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_set_region_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_get_region_rect
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "get_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_get_region_rect #-}

instance Method "get_region_rect" GodotSprite3D (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_get_region_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_set_frame
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "set_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_set_frame #-}

instance Method "set_frame" GodotSprite3D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_set_frame (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_get_frame
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "get_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_get_frame #-}

instance Method "get_frame" GodotSprite3D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_get_frame (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_set_vframes
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "set_vframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_set_vframes #-}

instance Method "set_vframes" GodotSprite3D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_set_vframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_get_vframes
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "get_vframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_get_vframes #-}

instance Method "get_vframes" GodotSprite3D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_get_vframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_set_hframes
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "set_hframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_set_hframes #-}

instance Method "set_hframes" GodotSprite3D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_set_hframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite3D_get_hframes
  = unsafePerformIO $
      withCString "Sprite3D" $
        \ clsNamePtr ->
          withCString "get_hframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite3D_get_hframes #-}

instance Method "get_hframes" GodotSprite3D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite3D_get_hframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimatedSprite3D = GodotAnimatedSprite3D GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotAnimatedSprite3D where
        type BaseClass GodotAnimatedSprite3D = GodotSpriteBase3D
        super = coerce
bindAnimatedSprite3D_set_sprite_frames
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "set_sprite_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_set_sprite_frames #-}

instance Method "set_sprite_frames" GodotAnimatedSprite3D
           (GodotSpriteFrames -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_set_sprite_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_get_sprite_frames
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "get_sprite_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_get_sprite_frames #-}

instance Method "get_sprite_frames" GodotAnimatedSprite3D
           (IO GodotSpriteFrames)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_get_sprite_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_set_animation
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "set_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_set_animation #-}

instance Method "set_animation" GodotAnimatedSprite3D
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_set_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_get_animation
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "get_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_get_animation #-}

instance Method "get_animation" GodotAnimatedSprite3D
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_get_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D__set_playing
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "_set_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D__set_playing #-}

instance Method "_set_playing" GodotAnimatedSprite3D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D__set_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D__is_playing
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "_is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D__is_playing #-}

instance Method "_is_playing" GodotAnimatedSprite3D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D__is_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_play
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_play #-}

instance Method "play" GodotAnimatedSprite3D (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_play (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_stop
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_stop #-}

instance Method "stop" GodotAnimatedSprite3D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_stop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_is_playing
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_is_playing #-}

instance Method "is_playing" GodotAnimatedSprite3D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_is_playing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_set_frame
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "set_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_set_frame #-}

instance Method "set_frame" GodotAnimatedSprite3D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_set_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D_get_frame
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "get_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D_get_frame #-}

instance Method "get_frame" GodotAnimatedSprite3D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D_get_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite3D__res_changed
  = unsafePerformIO $
      withCString "AnimatedSprite3D" $
        \ clsNamePtr ->
          withCString "_res_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite3D__res_changed #-}

instance Method "_res_changed" GodotAnimatedSprite3D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite3D__res_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpriteFrames = GodotSpriteFrames GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotSpriteFrames where
        type BaseClass GodotSpriteFrames = GodotResource
        super = coerce
bindSpriteFrames_add_animation
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "add_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_add_animation #-}

instance Method "add_animation" GodotSpriteFrames
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_add_animation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_has_animation
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "has_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_has_animation #-}

instance Method "has_animation" GodotSpriteFrames
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_has_animation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_remove_animation
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "remove_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_remove_animation #-}

instance Method "remove_animation" GodotSpriteFrames
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_remove_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_rename_animation
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "rename_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_rename_animation #-}

instance Method "rename_animation" GodotSpriteFrames
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_rename_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_get_animation_names
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "get_animation_names" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_get_animation_names #-}

instance Method "get_animation_names" GodotSpriteFrames
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_get_animation_names
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_set_animation_speed
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "set_animation_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_set_animation_speed #-}

instance Method "set_animation_speed" GodotSpriteFrames
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_set_animation_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_get_animation_speed
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "get_animation_speed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_get_animation_speed #-}

instance Method "get_animation_speed" GodotSpriteFrames
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_get_animation_speed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_set_animation_loop
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "set_animation_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_set_animation_loop #-}

instance Method "set_animation_loop" GodotSpriteFrames
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_set_animation_loop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_get_animation_loop
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "get_animation_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_get_animation_loop #-}

instance Method "get_animation_loop" GodotSpriteFrames
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_get_animation_loop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_add_frame
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "add_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_add_frame #-}

instance Method "add_frame" GodotSpriteFrames
           (GodotString -> GodotTexture -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_add_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_get_frame_count
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "get_frame_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_get_frame_count #-}

instance Method "get_frame_count" GodotSpriteFrames
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_get_frame_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_get_frame
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "get_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_get_frame #-}

instance Method "get_frame" GodotSpriteFrames
           (GodotString -> Int -> IO GodotTexture)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_get_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_set_frame
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "set_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_set_frame #-}

instance Method "set_frame" GodotSpriteFrames
           (GodotString -> Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_set_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_remove_frame
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "remove_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_remove_frame #-}

instance Method "remove_frame" GodotSpriteFrames
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_remove_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_clear
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_clear #-}

instance Method "clear" GodotSpriteFrames (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames_clear_all
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "clear_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames_clear_all #-}

instance Method "clear_all" GodotSpriteFrames (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames_clear_all (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames__set_frames
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "_set_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames__set_frames #-}

instance Method "_set_frames" GodotSpriteFrames
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames__set_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames__get_frames
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "_get_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames__get_frames #-}

instance Method "_get_frames" GodotSpriteFrames (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames__get_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames__set_animations
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "_set_animations" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames__set_animations #-}

instance Method "_set_animations" GodotSpriteFrames
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames__set_animations
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpriteFrames__get_animations
  = unsafePerformIO $
      withCString "SpriteFrames" $
        \ clsNamePtr ->
          withCString "_get_animations" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpriteFrames__get_animations #-}

instance Method "_get_animations" GodotSpriteFrames (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpriteFrames__get_animations
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotLight = GodotLight GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotLight where
        type BaseClass GodotLight = GodotVisualInstance
        super = coerce
bindLight_set_editor_only
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_editor_only" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_editor_only #-}

instance Method "set_editor_only" GodotLight (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_editor_only (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_is_editor_only
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "is_editor_only" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_is_editor_only #-}

instance Method "is_editor_only" GodotLight (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_is_editor_only (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_param
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_param #-}

instance Method "set_param" GodotLight (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_param (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_get_param
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_get_param #-}

instance Method "get_param" GodotLight (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_get_param (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_shadow
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_shadow" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_shadow #-}

instance Method "set_shadow" GodotLight (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_shadow (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_has_shadow
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "has_shadow" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_has_shadow #-}

instance Method "has_shadow" GodotLight (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_has_shadow (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_negative
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_negative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_negative #-}

instance Method "set_negative" GodotLight (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_negative (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_is_negative
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "is_negative" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_is_negative #-}

instance Method "is_negative" GodotLight (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_is_negative (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_cull_mask
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_cull_mask #-}

instance Method "set_cull_mask" GodotLight (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_cull_mask (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_get_cull_mask
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "get_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_get_cull_mask #-}

instance Method "get_cull_mask" GodotLight (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_get_cull_mask (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_color
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_color #-}

instance Method "set_color" GodotLight (GodotColor -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_color (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_get_color
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_get_color #-}

instance Method "get_color" GodotLight (IO GodotColor) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_get_color (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_shadow_reverse_cull_face
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_shadow_reverse_cull_face" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_shadow_reverse_cull_face #-}

instance Method "set_shadow_reverse_cull_face" GodotLight
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_shadow_reverse_cull_face
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_get_shadow_reverse_cull_face
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "get_shadow_reverse_cull_face" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_get_shadow_reverse_cull_face #-}

instance Method "get_shadow_reverse_cull_face" GodotLight (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_get_shadow_reverse_cull_face
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_shadow_color
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_shadow_color #-}

instance Method "set_shadow_color" GodotLight (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_shadow_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_get_shadow_color
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "get_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_get_shadow_color #-}

instance Method "get_shadow_color" GodotLight (IO GodotColor) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_get_shadow_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_set_bake_mode
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "set_bake_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_set_bake_mode #-}

instance Method "set_bake_mode" GodotLight (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_set_bake_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight_get_bake_mode
  = unsafePerformIO $
      withCString "Light" $
        \ clsNamePtr ->
          withCString "get_bake_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight_get_bake_mode #-}

instance Method "get_bake_mode" GodotLight (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight_get_bake_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotDirectionalLight = GodotDirectionalLight GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotDirectionalLight where
        type BaseClass GodotDirectionalLight = GodotLight
        super = coerce
bindDirectionalLight_get_param
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_get_param #-}

instance Method "get_param" GodotDirectionalLight (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_get_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDirectionalLight_set_param
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_set_param #-}

instance Method "set_param" GodotDirectionalLight (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_set_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDirectionalLight_set_shadow_mode
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "set_shadow_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_set_shadow_mode #-}

instance Method "set_shadow_mode" GodotDirectionalLight
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_set_shadow_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDirectionalLight_get_shadow_mode
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "get_shadow_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_get_shadow_mode #-}

instance Method "get_shadow_mode" GodotDirectionalLight (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_get_shadow_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDirectionalLight_set_shadow_depth_range
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "set_shadow_depth_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_set_shadow_depth_range #-}

instance Method "set_shadow_depth_range" GodotDirectionalLight
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_set_shadow_depth_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDirectionalLight_get_shadow_depth_range
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "get_shadow_depth_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_get_shadow_depth_range #-}

instance Method "get_shadow_depth_range" GodotDirectionalLight
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_get_shadow_depth_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDirectionalLight_set_blend_splits
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "set_blend_splits" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_set_blend_splits #-}

instance Method "set_blend_splits" GodotDirectionalLight
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_set_blend_splits
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDirectionalLight_is_blend_splits_enabled
  = unsafePerformIO $
      withCString "DirectionalLight" $
        \ clsNamePtr ->
          withCString "is_blend_splits_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDirectionalLight_is_blend_splits_enabled #-}

instance Method "is_blend_splits_enabled" GodotDirectionalLight
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDirectionalLight_is_blend_splits_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotOmniLight = GodotOmniLight GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotOmniLight where
        type BaseClass GodotOmniLight = GodotLight
        super = coerce
bindOmniLight_get_param
  = unsafePerformIO $
      withCString "OmniLight" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOmniLight_get_param #-}

instance Method "get_param" GodotOmniLight (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOmniLight_get_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOmniLight_set_param
  = unsafePerformIO $
      withCString "OmniLight" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOmniLight_set_param #-}

instance Method "set_param" GodotOmniLight (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOmniLight_set_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOmniLight_set_shadow_mode
  = unsafePerformIO $
      withCString "OmniLight" $
        \ clsNamePtr ->
          withCString "set_shadow_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOmniLight_set_shadow_mode #-}

instance Method "set_shadow_mode" GodotOmniLight (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOmniLight_set_shadow_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOmniLight_get_shadow_mode
  = unsafePerformIO $
      withCString "OmniLight" $
        \ clsNamePtr ->
          withCString "get_shadow_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOmniLight_get_shadow_mode #-}

instance Method "get_shadow_mode" GodotOmniLight (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOmniLight_get_shadow_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOmniLight_set_shadow_detail
  = unsafePerformIO $
      withCString "OmniLight" $
        \ clsNamePtr ->
          withCString "set_shadow_detail" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOmniLight_set_shadow_detail #-}

instance Method "set_shadow_detail" GodotOmniLight (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOmniLight_set_shadow_detail (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOmniLight_get_shadow_detail
  = unsafePerformIO $
      withCString "OmniLight" $
        \ clsNamePtr ->
          withCString "get_shadow_detail" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOmniLight_get_shadow_detail #-}

instance Method "get_shadow_detail" GodotOmniLight (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOmniLight_get_shadow_detail (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpotLight = GodotSpotLight GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotSpotLight where
        type BaseClass GodotSpotLight = GodotLight
        super = coerce
bindSpotLight_get_param
  = unsafePerformIO $
      withCString "SpotLight" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpotLight_get_param #-}

instance Method "get_param" GodotSpotLight (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpotLight_get_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpotLight_set_param
  = unsafePerformIO $
      withCString "SpotLight" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpotLight_set_param #-}

instance Method "set_param" GodotSpotLight (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpotLight_set_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotReflectionProbe = GodotReflectionProbe GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotReflectionProbe where
        type BaseClass GodotReflectionProbe = GodotVisualInstance
        super = coerce
bindReflectionProbe_set_intensity
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_intensity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_intensity #-}

instance Method "set_intensity" GodotReflectionProbe
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_intensity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_intensity
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_intensity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_intensity #-}

instance Method "get_intensity" GodotReflectionProbe (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_get_intensity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_interior_ambient
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_interior_ambient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_interior_ambient #-}

instance Method "set_interior_ambient" GodotReflectionProbe
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_interior_ambient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_interior_ambient
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_interior_ambient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_interior_ambient #-}

instance Method "get_interior_ambient" GodotReflectionProbe
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_get_interior_ambient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_interior_ambient_energy
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_interior_ambient_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_interior_ambient_energy #-}

instance Method "set_interior_ambient_energy" GodotReflectionProbe
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindReflectionProbe_set_interior_ambient_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_interior_ambient_energy
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_interior_ambient_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_interior_ambient_energy #-}

instance Method "get_interior_ambient_energy" GodotReflectionProbe
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindReflectionProbe_get_interior_ambient_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_interior_ambient_probe_contribution
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_interior_ambient_probe_contribution" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_interior_ambient_probe_contribution
             #-}

instance Method "set_interior_ambient_probe_contribution"
           GodotReflectionProbe
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindReflectionProbe_set_interior_ambient_probe_contribution
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_interior_ambient_probe_contribution
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_interior_ambient_probe_contribution" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_interior_ambient_probe_contribution
             #-}

instance Method "get_interior_ambient_probe_contribution"
           GodotReflectionProbe
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindReflectionProbe_get_interior_ambient_probe_contribution
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_max_distance
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_max_distance #-}

instance Method "set_max_distance" GodotReflectionProbe
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_max_distance
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_max_distance #-}

instance Method "get_max_distance" GodotReflectionProbe (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_get_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_extents
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_extents #-}

instance Method "set_extents" GodotReflectionProbe
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_extents (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_extents
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_extents #-}

instance Method "get_extents" GodotReflectionProbe
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_get_extents (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_origin_offset
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_origin_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_origin_offset #-}

instance Method "set_origin_offset" GodotReflectionProbe
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_origin_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_origin_offset
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_origin_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_origin_offset #-}

instance Method "get_origin_offset" GodotReflectionProbe
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_get_origin_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_as_interior
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_as_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_as_interior #-}

instance Method "set_as_interior" GodotReflectionProbe
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_as_interior
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_is_set_as_interior
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "is_set_as_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_is_set_as_interior #-}

instance Method "is_set_as_interior" GodotReflectionProbe (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_is_set_as_interior
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_enable_box_projection
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_enable_box_projection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_enable_box_projection #-}

instance Method "set_enable_box_projection" GodotReflectionProbe
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindReflectionProbe_set_enable_box_projection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_is_box_projection_enabled
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "is_box_projection_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_is_box_projection_enabled #-}

instance Method "is_box_projection_enabled" GodotReflectionProbe
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindReflectionProbe_is_box_projection_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_enable_shadows
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_enable_shadows" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_enable_shadows #-}

instance Method "set_enable_shadows" GodotReflectionProbe
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_enable_shadows
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_are_shadows_enabled
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "are_shadows_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_are_shadows_enabled #-}

instance Method "are_shadows_enabled" GodotReflectionProbe
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_are_shadows_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_cull_mask
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_cull_mask #-}

instance Method "set_cull_mask" GodotReflectionProbe (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_cull_mask
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_cull_mask #-}

instance Method "get_cull_mask" GodotReflectionProbe (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_get_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_set_update_mode
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "set_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_set_update_mode #-}

instance Method "set_update_mode" GodotReflectionProbe
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_set_update_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindReflectionProbe_get_update_mode
  = unsafePerformIO $
      withCString "ReflectionProbe" $
        \ clsNamePtr ->
          withCString "get_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindReflectionProbe_get_update_mode #-}

instance Method "get_update_mode" GodotReflectionProbe (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindReflectionProbe_get_update_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGIProbe = GodotGIProbe GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotGIProbe where
        type BaseClass GodotGIProbe = GodotVisualInstance
        super = coerce
bindGIProbe_set_probe_data
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_probe_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_probe_data #-}

instance Method "set_probe_data" GodotGIProbe
           (GodotGIProbeData -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_probe_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_probe_data
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_probe_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_probe_data #-}

instance Method "get_probe_data" GodotGIProbe (IO GodotGIProbeData)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_probe_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_subdiv
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_subdiv #-}

instance Method "set_subdiv" GodotGIProbe (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_subdiv (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_subdiv
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_subdiv #-}

instance Method "get_subdiv" GodotGIProbe (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_subdiv (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_extents
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_extents #-}

instance Method "set_extents" GodotGIProbe (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_extents (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_extents
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_extents #-}

instance Method "get_extents" GodotGIProbe (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_extents (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_dynamic_range
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_dynamic_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_dynamic_range #-}

instance Method "set_dynamic_range" GodotGIProbe (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_dynamic_range (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_dynamic_range
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_dynamic_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_dynamic_range #-}

instance Method "get_dynamic_range" GodotGIProbe (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_dynamic_range (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_energy
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_energy #-}

instance Method "set_energy" GodotGIProbe (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_energy (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_energy
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_energy #-}

instance Method "get_energy" GodotGIProbe (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_energy (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_bias
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_bias #-}

instance Method "set_bias" GodotGIProbe (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_bias (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_bias
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_bias #-}

instance Method "get_bias" GodotGIProbe (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_bias (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_normal_bias
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_normal_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_normal_bias #-}

instance Method "set_normal_bias" GodotGIProbe (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_normal_bias (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_normal_bias
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_normal_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_normal_bias #-}

instance Method "get_normal_bias" GodotGIProbe (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_normal_bias (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_propagation
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_propagation #-}

instance Method "set_propagation" GodotGIProbe (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_propagation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_get_propagation
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "get_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_get_propagation #-}

instance Method "get_propagation" GodotGIProbe (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_get_propagation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_interior
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_interior #-}

instance Method "set_interior" GodotGIProbe (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_interior (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_is_interior
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "is_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_is_interior #-}

instance Method "is_interior" GodotGIProbe (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_is_interior (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_set_compress
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "set_compress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_set_compress #-}

instance Method "set_compress" GodotGIProbe (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_set_compress (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_is_compressed
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "is_compressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_is_compressed #-}

instance Method "is_compressed" GodotGIProbe (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_is_compressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_bake
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "bake" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_bake #-}

instance Method "bake" GodotGIProbe (GodotObject -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_bake (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbe_debug_bake
  = unsafePerformIO $
      withCString "GIProbe" $
        \ clsNamePtr ->
          withCString "debug_bake" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbe_debug_bake #-}

instance Method "debug_bake" GodotGIProbe (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbe_debug_bake (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGIProbeData = GodotGIProbeData GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotGIProbeData where
        type BaseClass GodotGIProbeData = GodotResource
        super = coerce
bindGIProbeData_set_bounds
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_bounds #-}

instance Method "set_bounds" GodotGIProbeData (GodotAabb -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_bounds (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_bounds
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_bounds #-}

instance Method "get_bounds" GodotGIProbeData (IO GodotAabb) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_bounds (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_cell_size
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_cell_size #-}

instance Method "set_cell_size" GodotGIProbeData (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_cell_size
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_cell_size #-}

instance Method "get_cell_size" GodotGIProbeData (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_to_cell_xform
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_to_cell_xform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_to_cell_xform #-}

instance Method "set_to_cell_xform" GodotGIProbeData
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_to_cell_xform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_to_cell_xform
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_to_cell_xform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_to_cell_xform #-}

instance Method "get_to_cell_xform" GodotGIProbeData
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_to_cell_xform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_dynamic_data
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_dynamic_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_dynamic_data #-}

instance Method "set_dynamic_data" GodotGIProbeData
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_dynamic_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_dynamic_data
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_dynamic_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_dynamic_data #-}

instance Method "get_dynamic_data" GodotGIProbeData
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_dynamic_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_dynamic_range
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_dynamic_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_dynamic_range #-}

instance Method "set_dynamic_range" GodotGIProbeData (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_dynamic_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_dynamic_range
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_dynamic_range" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_dynamic_range #-}

instance Method "get_dynamic_range" GodotGIProbeData (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_dynamic_range
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_energy
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_energy #-}

instance Method "set_energy" GodotGIProbeData (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_energy (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_energy
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_energy #-}

instance Method "get_energy" GodotGIProbeData (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_energy (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_bias
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_bias #-}

instance Method "set_bias" GodotGIProbeData (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_bias (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_bias
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_bias #-}

instance Method "get_bias" GodotGIProbeData (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_bias (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_normal_bias
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_normal_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_normal_bias #-}

instance Method "set_normal_bias" GodotGIProbeData (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_normal_bias (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_normal_bias
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_normal_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_normal_bias #-}

instance Method "get_normal_bias" GodotGIProbeData (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_normal_bias (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_propagation
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_propagation #-}

instance Method "set_propagation" GodotGIProbeData (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_propagation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_get_propagation
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "get_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_get_propagation #-}

instance Method "get_propagation" GodotGIProbeData (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_get_propagation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_interior
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_interior #-}

instance Method "set_interior" GodotGIProbeData (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_interior (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_is_interior
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "is_interior" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_is_interior #-}

instance Method "is_interior" GodotGIProbeData (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_is_interior (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_set_compress
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "set_compress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_set_compress #-}

instance Method "set_compress" GodotGIProbeData (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_set_compress (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGIProbeData_is_compressed
  = unsafePerformIO $
      withCString "GIProbeData" $
        \ clsNamePtr ->
          withCString "is_compressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGIProbeData_is_compressed #-}

instance Method "is_compressed" GodotGIProbeData (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGIProbeData_is_compressed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBakedLightmap = GodotBakedLightmap GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotBakedLightmap where
        type BaseClass GodotBakedLightmap = GodotVisualInstance
        super = coerce
bindBakedLightmap_set_light_data
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_light_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_light_data #-}

instance Method "set_light_data" GodotBakedLightmap
           (GodotBakedLightmapData -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_light_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_light_data
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_light_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_light_data #-}

instance Method "get_light_data" GodotBakedLightmap
           (IO GodotBakedLightmapData)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_light_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_bake_cell_size
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_bake_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_bake_cell_size #-}

instance Method "set_bake_cell_size" GodotBakedLightmap
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_bake_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_bake_cell_size
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_bake_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_bake_cell_size #-}

instance Method "get_bake_cell_size" GodotBakedLightmap (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_bake_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_capture_cell_size
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_capture_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_capture_cell_size #-}

instance Method "set_capture_cell_size" GodotBakedLightmap
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_capture_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_capture_cell_size
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_capture_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_capture_cell_size #-}

instance Method "get_capture_cell_size" GodotBakedLightmap
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_capture_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_bake_quality
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_bake_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_bake_quality #-}

instance Method "set_bake_quality" GodotBakedLightmap
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_bake_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_bake_quality
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_bake_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_bake_quality #-}

instance Method "get_bake_quality" GodotBakedLightmap (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_bake_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_bake_mode
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_bake_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_bake_mode #-}

instance Method "set_bake_mode" GodotBakedLightmap (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_bake_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_bake_mode
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_bake_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_bake_mode #-}

instance Method "get_bake_mode" GodotBakedLightmap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_bake_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_extents
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_extents #-}

instance Method "set_extents" GodotBakedLightmap
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_extents (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_extents
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_extents #-}

instance Method "get_extents" GodotBakedLightmap (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_extents (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_propagation
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_propagation #-}

instance Method "set_propagation" GodotBakedLightmap
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_propagation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_propagation
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_propagation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_propagation #-}

instance Method "get_propagation" GodotBakedLightmap (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_propagation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_energy
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_energy #-}

instance Method "set_energy" GodotBakedLightmap (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_energy (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_energy
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_energy #-}

instance Method "get_energy" GodotBakedLightmap (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_energy (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_hdr
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_hdr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_hdr #-}

instance Method "set_hdr" GodotBakedLightmap (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_hdr (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_is_hdr
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "is_hdr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_is_hdr #-}

instance Method "is_hdr" GodotBakedLightmap (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_is_hdr (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_set_image_path
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "set_image_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_set_image_path #-}

instance Method "set_image_path" GodotBakedLightmap
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_set_image_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_get_image_path
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "get_image_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_get_image_path #-}

instance Method "get_image_path" GodotBakedLightmap
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_get_image_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_bake
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "bake" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_bake #-}

instance Method "bake" GodotBakedLightmap
           (GodotObject -> Bool -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_bake (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmap_debug_bake
  = unsafePerformIO $
      withCString "BakedLightmap" $
        \ clsNamePtr ->
          withCString "debug_bake" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmap_debug_bake #-}

instance Method "debug_bake" GodotBakedLightmap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmap_debug_bake (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBakedLightmapData = GodotBakedLightmapData GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotBakedLightmapData where
        type BaseClass GodotBakedLightmapData = GodotResource
        super = coerce
bindBakedLightmapData__set_user_data
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "_set_user_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData__set_user_data #-}

instance Method "_set_user_data" GodotBakedLightmapData
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData__set_user_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData__get_user_data
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "_get_user_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData__get_user_data #-}

instance Method "_get_user_data" GodotBakedLightmapData
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData__get_user_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_set_bounds
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "set_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_set_bounds #-}

instance Method "set_bounds" GodotBakedLightmapData
           (GodotAabb -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_set_bounds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_bounds
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_bounds #-}

instance Method "get_bounds" GodotBakedLightmapData (IO GodotAabb)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_get_bounds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_set_cell_space_transform
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "set_cell_space_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_set_cell_space_transform #-}

instance Method "set_cell_space_transform" GodotBakedLightmapData
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindBakedLightmapData_set_cell_space_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_cell_space_transform
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_cell_space_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_cell_space_transform #-}

instance Method "get_cell_space_transform" GodotBakedLightmapData
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindBakedLightmapData_get_cell_space_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_set_cell_subdiv
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "set_cell_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_set_cell_subdiv #-}

instance Method "set_cell_subdiv" GodotBakedLightmapData
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_set_cell_subdiv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_cell_subdiv
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_cell_subdiv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_cell_subdiv #-}

instance Method "get_cell_subdiv" GodotBakedLightmapData (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_get_cell_subdiv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_set_octree
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "set_octree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_set_octree #-}

instance Method "set_octree" GodotBakedLightmapData
           (GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_set_octree
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_octree
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_octree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_octree #-}

instance Method "get_octree" GodotBakedLightmapData
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_get_octree
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_set_energy
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_set_energy #-}

instance Method "set_energy" GodotBakedLightmapData
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_set_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_energy
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_energy #-}

instance Method "get_energy" GodotBakedLightmapData (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_get_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_add_user
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "add_user" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_add_user #-}

instance Method "add_user" GodotBakedLightmapData
           (GodotNodePath -> GodotTexture -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_add_user (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_user_count
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_user_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_user_count #-}

instance Method "get_user_count" GodotBakedLightmapData (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_get_user_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_user_path
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_user_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_user_path #-}

instance Method "get_user_path" GodotBakedLightmapData
           (Int -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_get_user_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_get_user_lightmap
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "get_user_lightmap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_get_user_lightmap #-}

instance Method "get_user_lightmap" GodotBakedLightmapData
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_get_user_lightmap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBakedLightmapData_clear_users
  = unsafePerformIO $
      withCString "BakedLightmapData" $
        \ clsNamePtr ->
          withCString "clear_users" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBakedLightmapData_clear_users #-}

instance Method "clear_users" GodotBakedLightmapData (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBakedLightmapData_clear_users
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationTreePlayer = GodotAnimationTreePlayer GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotAnimationTreePlayer where
        type BaseClass GodotAnimationTreePlayer = GodotNode
        super = coerce
bindAnimationTreePlayer_add_node
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "add_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_add_node #-}

instance Method "add_node" GodotAnimationTreePlayer
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_add_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_node_exists
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "node_exists" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_node_exists #-}

instance Method "node_exists" GodotAnimationTreePlayer
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_node_exists
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_node_rename
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "node_rename" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_node_rename #-}

instance Method "node_rename" GodotAnimationTreePlayer
           (GodotString -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_node_rename
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_node_get_type
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "node_get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_node_get_type #-}

instance Method "node_get_type" GodotAnimationTreePlayer
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_node_get_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_node_get_input_count
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "node_get_input_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_node_get_input_count #-}

instance Method "node_get_input_count" GodotAnimationTreePlayer
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_node_get_input_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_node_get_input_source
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "node_get_input_source" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_node_get_input_source #-}

instance Method "node_get_input_source" GodotAnimationTreePlayer
           (GodotString -> Int -> IO GodotString)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_node_get_input_source
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_animation_node_set_animation
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "animation_node_set_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_animation_node_set_animation
             #-}

instance Method "animation_node_set_animation"
           GodotAnimationTreePlayer
           (GodotString -> GodotAnimation -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_animation_node_set_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_animation_node_get_animation
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "animation_node_get_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_animation_node_get_animation
             #-}

instance Method "animation_node_get_animation"
           GodotAnimationTreePlayer
           (GodotString -> IO GodotAnimation)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_animation_node_get_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_animation_node_set_master_animation
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "animation_node_set_master_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_animation_node_set_master_animation
             #-}

instance Method "animation_node_set_master_animation"
           GodotAnimationTreePlayer
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_animation_node_set_master_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_animation_node_get_master_animation
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "animation_node_get_master_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_animation_node_get_master_animation
             #-}

instance Method "animation_node_get_master_animation"
           GodotAnimationTreePlayer
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_animation_node_get_master_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_animation_node_get_position
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "animation_node_get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_animation_node_get_position
             #-}

instance Method "animation_node_get_position"
           GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_animation_node_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_animation_node_set_filter_path
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "animation_node_set_filter_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_animation_node_set_filter_path
             #-}

instance Method "animation_node_set_filter_path"
           GodotAnimationTreePlayer
           (GodotString -> GodotNodePath -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_animation_node_set_filter_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_set_fadein_time
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_set_fadein_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_set_fadein_time
             #-}

instance Method "oneshot_node_set_fadein_time"
           GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_set_fadein_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_get_fadein_time
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_get_fadein_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_get_fadein_time
             #-}

instance Method "oneshot_node_get_fadein_time"
           GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_get_fadein_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_set_fadeout_time
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_set_fadeout_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_set_fadeout_time
             #-}

instance Method "oneshot_node_set_fadeout_time"
           GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_set_fadeout_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_get_fadeout_time
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_get_fadeout_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_get_fadeout_time
             #-}

instance Method "oneshot_node_get_fadeout_time"
           GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_get_fadeout_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_set_autorestart
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_set_autorestart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_set_autorestart
             #-}

instance Method "oneshot_node_set_autorestart"
           GodotAnimationTreePlayer
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_set_autorestart
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_set_autorestart_delay
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_set_autorestart_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_set_autorestart_delay
             #-}

instance Method "oneshot_node_set_autorestart_delay"
           GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_set_autorestart_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_set_autorestart_random_delay
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_set_autorestart_random_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_set_autorestart_random_delay
             #-}

instance Method "oneshot_node_set_autorestart_random_delay"
           GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_set_autorestart_random_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_has_autorestart
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_has_autorestart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_has_autorestart
             #-}

instance Method "oneshot_node_has_autorestart"
           GodotAnimationTreePlayer
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_has_autorestart
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_get_autorestart_delay
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_get_autorestart_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_get_autorestart_delay
             #-}

instance Method "oneshot_node_get_autorestart_delay"
           GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_get_autorestart_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_get_autorestart_random_delay
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_get_autorestart_random_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_get_autorestart_random_delay
             #-}

instance Method "oneshot_node_get_autorestart_random_delay"
           GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_get_autorestart_random_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_start
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_start #-}

instance Method "oneshot_node_start" GodotAnimationTreePlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_oneshot_node_start
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_stop
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_stop #-}

instance Method "oneshot_node_stop" GodotAnimationTreePlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_oneshot_node_stop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_is_active
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_is_active #-}

instance Method "oneshot_node_is_active" GodotAnimationTreePlayer
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_oneshot_node_set_filter_path
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "oneshot_node_set_filter_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_oneshot_node_set_filter_path
             #-}

instance Method "oneshot_node_set_filter_path"
           GodotAnimationTreePlayer
           (GodotString -> GodotNodePath -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_oneshot_node_set_filter_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_mix_node_set_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "mix_node_set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_mix_node_set_amount #-}

instance Method "mix_node_set_amount" GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_mix_node_set_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_mix_node_get_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "mix_node_get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_mix_node_get_amount #-}

instance Method "mix_node_get_amount" GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_mix_node_get_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_blend2_node_set_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "blend2_node_set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_blend2_node_set_amount #-}

instance Method "blend2_node_set_amount" GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_blend2_node_set_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_blend2_node_get_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "blend2_node_get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_blend2_node_get_amount #-}

instance Method "blend2_node_get_amount" GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_blend2_node_get_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_blend2_node_set_filter_path
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "blend2_node_set_filter_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_blend2_node_set_filter_path
             #-}

instance Method "blend2_node_set_filter_path"
           GodotAnimationTreePlayer
           (GodotString -> GodotNodePath -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_blend2_node_set_filter_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_blend3_node_set_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "blend3_node_set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_blend3_node_set_amount #-}

instance Method "blend3_node_set_amount" GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_blend3_node_set_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_blend3_node_get_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "blend3_node_get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_blend3_node_get_amount #-}

instance Method "blend3_node_get_amount" GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_blend3_node_get_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_blend4_node_set_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "blend4_node_set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_blend4_node_set_amount #-}

instance Method "blend4_node_set_amount" GodotAnimationTreePlayer
           (GodotString -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_blend4_node_set_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_blend4_node_get_amount
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "blend4_node_get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_blend4_node_get_amount #-}

instance Method "blend4_node_get_amount" GodotAnimationTreePlayer
           (GodotString -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_blend4_node_get_amount
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_timescale_node_set_scale
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "timescale_node_set_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_timescale_node_set_scale #-}

instance Method "timescale_node_set_scale" GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_timescale_node_set_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_timescale_node_get_scale
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "timescale_node_get_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_timescale_node_get_scale #-}

instance Method "timescale_node_get_scale" GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_timescale_node_get_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_timeseek_node_seek
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "timeseek_node_seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_timeseek_node_seek #-}

instance Method "timeseek_node_seek" GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_timeseek_node_seek
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_set_input_count
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_set_input_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_set_input_count
             #-}

instance Method "transition_node_set_input_count"
           GodotAnimationTreePlayer
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_set_input_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_get_input_count
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_get_input_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_get_input_count
             #-}

instance Method "transition_node_get_input_count"
           GodotAnimationTreePlayer
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_get_input_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_delete_input
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_delete_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_delete_input
             #-}

instance Method "transition_node_delete_input"
           GodotAnimationTreePlayer
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_delete_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_set_input_auto_advance
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_set_input_auto_advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_set_input_auto_advance
             #-}

instance Method "transition_node_set_input_auto_advance"
           GodotAnimationTreePlayer
           (GodotString -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_set_input_auto_advance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_has_input_auto_advance
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_has_input_auto_advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_has_input_auto_advance
             #-}

instance Method "transition_node_has_input_auto_advance"
           GodotAnimationTreePlayer
           (GodotString -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_has_input_auto_advance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_set_xfade_time
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_set_xfade_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_set_xfade_time
             #-}

instance Method "transition_node_set_xfade_time"
           GodotAnimationTreePlayer
           (GodotString -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_set_xfade_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_get_xfade_time
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_get_xfade_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_get_xfade_time
             #-}

instance Method "transition_node_get_xfade_time"
           GodotAnimationTreePlayer
           (GodotString -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_get_xfade_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_set_current
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_set_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_set_current
             #-}

instance Method "transition_node_set_current"
           GodotAnimationTreePlayer
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_set_current
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_transition_node_get_current
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "transition_node_get_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_transition_node_get_current
             #-}

instance Method "transition_node_get_current"
           GodotAnimationTreePlayer
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_transition_node_get_current
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_node_set_position
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "node_set_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_node_set_position #-}

instance Method "node_set_position" GodotAnimationTreePlayer
           (GodotString -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_node_set_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_node_get_position
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "node_get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_node_get_position #-}

instance Method "node_get_position" GodotAnimationTreePlayer
           (GodotString -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_node_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_remove_node
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "remove_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_remove_node #-}

instance Method "remove_node" GodotAnimationTreePlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_remove_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_connect_nodes
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "connect_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_connect_nodes #-}

instance Method "connect_nodes" GodotAnimationTreePlayer
           (GodotString -> GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_connect_nodes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_are_nodes_connected
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "are_nodes_connected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_are_nodes_connected #-}

instance Method "are_nodes_connected" GodotAnimationTreePlayer
           (GodotString -> GodotString -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_are_nodes_connected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_disconnect_nodes
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "disconnect_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_disconnect_nodes #-}

instance Method "disconnect_nodes" GodotAnimationTreePlayer
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_disconnect_nodes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_set_active
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_set_active #-}

instance Method "set_active" GodotAnimationTreePlayer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_set_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_is_active
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_is_active #-}

instance Method "is_active" GodotAnimationTreePlayer (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_set_base_path
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "set_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_set_base_path #-}

instance Method "set_base_path" GodotAnimationTreePlayer
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_set_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_get_base_path
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "get_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_get_base_path #-}

instance Method "get_base_path" GodotAnimationTreePlayer
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_get_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_set_master_player
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "set_master_player" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_set_master_player #-}

instance Method "set_master_player" GodotAnimationTreePlayer
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_set_master_player
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_get_master_player
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "get_master_player" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_get_master_player #-}

instance Method "get_master_player" GodotAnimationTreePlayer
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_get_master_player
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_get_node_list
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "get_node_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_get_node_list #-}

instance Method "get_node_list" GodotAnimationTreePlayer
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_get_node_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_set_animation_process_mode
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "set_animation_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_set_animation_process_mode #-}

instance Method "set_animation_process_mode"
           GodotAnimationTreePlayer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_set_animation_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_get_animation_process_mode
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "get_animation_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_get_animation_process_mode #-}

instance Method "get_animation_process_mode"
           GodotAnimationTreePlayer
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationTreePlayer_get_animation_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_advance
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_advance #-}

instance Method "advance" GodotAnimationTreePlayer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_advance (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_reset
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "reset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_reset #-}

instance Method "reset" GodotAnimationTreePlayer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_reset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTreePlayer_recompute_caches
  = unsafePerformIO $
      withCString "AnimationTreePlayer" $
        \ clsNamePtr ->
          withCString "recompute_caches" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTreePlayer_recompute_caches #-}

instance Method "recompute_caches" GodotAnimationTreePlayer (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTreePlayer_recompute_caches
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotParticles = GodotParticles GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotParticles where
        type BaseClass GodotParticles = GodotGeometryInstance
        super = coerce
bindParticles_set_emitting
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_emitting #-}

instance Method "set_emitting" GodotParticles (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_amount
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_amount #-}

instance Method "set_amount" GodotParticles (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_amount (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_lifetime
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_lifetime #-}

instance Method "set_lifetime" GodotParticles (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_one_shot
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_one_shot #-}

instance Method "set_one_shot" GodotParticles (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_pre_process_time
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_pre_process_time #-}

instance Method "set_pre_process_time" GodotParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_explosiveness_ratio
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_explosiveness_ratio #-}

instance Method "set_explosiveness_ratio" GodotParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_randomness_ratio
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_randomness_ratio #-}

instance Method "set_randomness_ratio" GodotParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_visibility_aabb
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_visibility_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_visibility_aabb #-}

instance Method "set_visibility_aabb" GodotParticles
           (GodotAabb -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_visibility_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_use_local_coordinates
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_use_local_coordinates #-}

instance Method "set_use_local_coordinates" GodotParticles
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_fixed_fps
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_fixed_fps #-}

instance Method "set_fixed_fps" GodotParticles (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_fixed_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_fractional_delta
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_fractional_delta #-}

instance Method "set_fractional_delta" GodotParticles
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_process_material
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_process_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_process_material #-}

instance Method "set_process_material" GodotParticles
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_process_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_speed_scale
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_speed_scale #-}

instance Method "set_speed_scale" GodotParticles (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_speed_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_is_emitting
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "is_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_is_emitting #-}

instance Method "is_emitting" GodotParticles (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_is_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_amount
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_amount #-}

instance Method "get_amount" GodotParticles (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_amount (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_lifetime
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_lifetime #-}

instance Method "get_lifetime" GodotParticles (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_one_shot
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_one_shot #-}

instance Method "get_one_shot" GodotParticles (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_pre_process_time
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_pre_process_time #-}

instance Method "get_pre_process_time" GodotParticles (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_explosiveness_ratio
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_explosiveness_ratio #-}

instance Method "get_explosiveness_ratio" GodotParticles (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_randomness_ratio
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_randomness_ratio #-}

instance Method "get_randomness_ratio" GodotParticles (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_visibility_aabb
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_visibility_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_visibility_aabb #-}

instance Method "get_visibility_aabb" GodotParticles (IO GodotAabb)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_visibility_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_use_local_coordinates
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_use_local_coordinates #-}

instance Method "get_use_local_coordinates" GodotParticles
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_fixed_fps
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_fixed_fps #-}

instance Method "get_fixed_fps" GodotParticles (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_fixed_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_fractional_delta
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_fractional_delta #-}

instance Method "get_fractional_delta" GodotParticles (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_process_material
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_process_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_process_material #-}

instance Method "get_process_material" GodotParticles
           (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_process_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_speed_scale
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_speed_scale #-}

instance Method "get_speed_scale" GodotParticles (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_speed_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_draw_order
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_draw_order #-}

instance Method "set_draw_order" GodotParticles (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_draw_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_draw_order
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_draw_order #-}

instance Method "get_draw_order" GodotParticles (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_draw_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_draw_passes
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_draw_passes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_draw_passes #-}

instance Method "set_draw_passes" GodotParticles (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_draw_passes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_set_draw_pass_mesh
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "set_draw_pass_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_set_draw_pass_mesh #-}

instance Method "set_draw_pass_mesh" GodotParticles
           (Int -> GodotMesh -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_set_draw_pass_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_draw_passes
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_draw_passes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_draw_passes #-}

instance Method "get_draw_passes" GodotParticles (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_draw_passes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_get_draw_pass_mesh
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "get_draw_pass_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_get_draw_pass_mesh #-}

instance Method "get_draw_pass_mesh" GodotParticles
           (Int -> IO GodotMesh)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_get_draw_pass_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_restart
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "restart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_restart #-}

instance Method "restart" GodotParticles (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_restart (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles_capture_aabb
  = unsafePerformIO $
      withCString "Particles" $
        \ clsNamePtr ->
          withCString "capture_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles_capture_aabb #-}

instance Method "capture_aabb" GodotParticles (IO GodotAabb) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles_capture_aabb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCPUParticles = GodotCPUParticles GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotCPUParticles where
        type BaseClass GodotCPUParticles = GodotGeometryInstance
        super = coerce
bindCPUParticles_set_emitting
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_emitting #-}

instance Method "set_emitting" GodotCPUParticles (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_amount
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_amount #-}

instance Method "set_amount" GodotCPUParticles (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_lifetime
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_lifetime #-}

instance Method "set_lifetime" GodotCPUParticles (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_one_shot
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_one_shot #-}

instance Method "set_one_shot" GodotCPUParticles (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_pre_process_time
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_pre_process_time #-}

instance Method "set_pre_process_time" GodotCPUParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_explosiveness_ratio
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_explosiveness_ratio #-}

instance Method "set_explosiveness_ratio" GodotCPUParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_randomness_ratio
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_randomness_ratio #-}

instance Method "set_randomness_ratio" GodotCPUParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_use_local_coordinates
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_use_local_coordinates #-}

instance Method "set_use_local_coordinates" GodotCPUParticles
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_fixed_fps
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_fixed_fps #-}

instance Method "set_fixed_fps" GodotCPUParticles (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_fixed_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_fractional_delta
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_fractional_delta #-}

instance Method "set_fractional_delta" GodotCPUParticles
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_speed_scale
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_speed_scale #-}

instance Method "set_speed_scale" GodotCPUParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_is_emitting
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "is_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_is_emitting #-}

instance Method "is_emitting" GodotCPUParticles (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_is_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_amount
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_amount #-}

instance Method "get_amount" GodotCPUParticles (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_lifetime
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_lifetime #-}

instance Method "get_lifetime" GodotCPUParticles (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_one_shot
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_one_shot #-}

instance Method "get_one_shot" GodotCPUParticles (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_pre_process_time
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_pre_process_time #-}

instance Method "get_pre_process_time" GodotCPUParticles (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_explosiveness_ratio
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_explosiveness_ratio #-}

instance Method "get_explosiveness_ratio" GodotCPUParticles
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_randomness_ratio
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_randomness_ratio #-}

instance Method "get_randomness_ratio" GodotCPUParticles (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_use_local_coordinates
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_use_local_coordinates #-}

instance Method "get_use_local_coordinates" GodotCPUParticles
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_fixed_fps
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_fixed_fps #-}

instance Method "get_fixed_fps" GodotCPUParticles (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_fixed_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_fractional_delta
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_fractional_delta #-}

instance Method "get_fractional_delta" GodotCPUParticles (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_speed_scale
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_speed_scale #-}

instance Method "get_speed_scale" GodotCPUParticles (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_draw_order
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_draw_order #-}

instance Method "set_draw_order" GodotCPUParticles (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_draw_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_draw_order
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_draw_order #-}

instance Method "get_draw_order" GodotCPUParticles (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_draw_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_mesh
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_mesh #-}

instance Method "set_mesh" GodotCPUParticles (GodotMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_mesh
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_mesh #-}

instance Method "get_mesh" GodotCPUParticles (IO GodotMesh) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_restart
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "restart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_restart #-}

instance Method "restart" GodotCPUParticles (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_restart (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_spread
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_spread #-}

instance Method "set_spread" GodotCPUParticles (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_spread (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_spread
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_spread #-}

instance Method "get_spread" GodotCPUParticles (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_spread (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_flatness
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_flatness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_flatness #-}

instance Method "set_flatness" GodotCPUParticles (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_flatness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_flatness
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_flatness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_flatness #-}

instance Method "get_flatness" GodotCPUParticles (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_flatness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_param
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_param #-}

instance Method "set_param" GodotCPUParticles
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_param
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_param #-}

instance Method "get_param" GodotCPUParticles (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_param_randomness
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_param_randomness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_param_randomness #-}

instance Method "set_param_randomness" GodotCPUParticles
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_param_randomness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_param_randomness
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_param_randomness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_param_randomness #-}

instance Method "get_param_randomness" GodotCPUParticles
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_param_randomness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_param_curve
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_param_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_param_curve #-}

instance Method "set_param_curve" GodotCPUParticles
           (Int -> GodotCurve -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_param_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_param_curve
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_param_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_param_curve #-}

instance Method "get_param_curve" GodotCPUParticles
           (Int -> IO GodotCurve)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_param_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_color
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_color #-}

instance Method "set_color" GodotCPUParticles (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_color
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_color #-}

instance Method "get_color" GodotCPUParticles (IO GodotColor) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_color_ramp
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_color_ramp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_color_ramp #-}

instance Method "set_color_ramp" GodotCPUParticles
           (GodotGradient -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_color_ramp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_color_ramp
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_color_ramp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_color_ramp #-}

instance Method "get_color_ramp" GodotCPUParticles
           (IO GodotGradient)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_color_ramp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_particle_flag
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_particle_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_particle_flag #-}

instance Method "set_particle_flag" GodotCPUParticles
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_particle_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_particle_flag
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_particle_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_particle_flag #-}

instance Method "get_particle_flag" GodotCPUParticles
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_particle_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_emission_shape
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_emission_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_emission_shape #-}

instance Method "set_emission_shape" GodotCPUParticles
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_emission_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_emission_shape
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_emission_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_emission_shape #-}

instance Method "get_emission_shape" GodotCPUParticles (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_emission_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_emission_sphere_radius
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_emission_sphere_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_emission_sphere_radius #-}

instance Method "set_emission_sphere_radius" GodotCPUParticles
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_emission_sphere_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_emission_sphere_radius
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_emission_sphere_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_emission_sphere_radius #-}

instance Method "get_emission_sphere_radius" GodotCPUParticles
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_emission_sphere_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_emission_box_extents
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_emission_box_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_emission_box_extents #-}

instance Method "set_emission_box_extents" GodotCPUParticles
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_emission_box_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_emission_box_extents
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_emission_box_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_emission_box_extents #-}

instance Method "get_emission_box_extents" GodotCPUParticles
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_emission_box_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_emission_points
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_emission_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_emission_points #-}

instance Method "set_emission_points" GodotCPUParticles
           (GodotPoolVector3Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_emission_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_emission_points
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_emission_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_emission_points #-}

instance Method "get_emission_points" GodotCPUParticles
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_emission_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_emission_normals
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_emission_normals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_emission_normals #-}

instance Method "set_emission_normals" GodotCPUParticles
           (GodotPoolVector3Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_emission_normals
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_emission_normals
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_emission_normals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_emission_normals #-}

instance Method "get_emission_normals" GodotCPUParticles
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_emission_normals
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_emission_colors
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_emission_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_emission_colors #-}

instance Method "set_emission_colors" GodotCPUParticles
           (GodotPoolColorArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_emission_colors
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_emission_colors
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_emission_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_emission_colors #-}

instance Method "get_emission_colors" GodotCPUParticles
           (IO GodotPoolColorArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_emission_colors
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_get_gravity
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "get_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_get_gravity #-}

instance Method "get_gravity" GodotCPUParticles (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_get_gravity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_set_gravity
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "set_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_set_gravity #-}

instance Method "set_gravity" GodotCPUParticles
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_set_gravity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles_convert_from_particles
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "convert_from_particles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles_convert_from_particles #-}

instance Method "convert_from_particles" GodotCPUParticles
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles_convert_from_particles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles__update_render_thread
  = unsafePerformIO $
      withCString "CPUParticles" $
        \ clsNamePtr ->
          withCString "_update_render_thread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles__update_render_thread #-}

instance Method "_update_render_thread" GodotCPUParticles (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles__update_render_thread
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCurve = GodotCurve GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotCurve where
        type BaseClass GodotCurve = GodotResource
        super = coerce
bindCurve_get_point_count
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_point_count #-}

instance Method "get_point_count" GodotCurve (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_point_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_add_point
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "add_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_add_point #-}

instance Method "add_point" GodotCurve
           (GodotVector2 -> Float -> Float -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_add_point (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_remove_point
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "remove_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_remove_point #-}

instance Method "remove_point" GodotCurve (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_remove_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_clear_points
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "clear_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_clear_points #-}

instance Method "clear_points" GodotCurve (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_clear_points (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_point_position
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_point_position #-}

instance Method "get_point_position" GodotCurve
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_point_value
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_point_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_point_value #-}

instance Method "set_point_value" GodotCurve
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_point_value (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_point_offset
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_point_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_point_offset #-}

instance Method "set_point_offset" GodotCurve
           (Int -> Float -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_point_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_interpolate
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "interpolate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_interpolate #-}

instance Method "interpolate" GodotCurve (Float -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_interpolate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_interpolate_baked
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "interpolate_baked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_interpolate_baked #-}

instance Method "interpolate_baked" GodotCurve (Float -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_interpolate_baked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_point_left_tangent
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_point_left_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_point_left_tangent #-}

instance Method "get_point_left_tangent" GodotCurve
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_point_left_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_point_right_tangent
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_point_right_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_point_right_tangent #-}

instance Method "get_point_right_tangent" GodotCurve
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_point_right_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_point_left_mode
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_point_left_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_point_left_mode #-}

instance Method "get_point_left_mode" GodotCurve (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_point_left_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_point_right_mode
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_point_right_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_point_right_mode #-}

instance Method "get_point_right_mode" GodotCurve (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_point_right_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_point_left_tangent
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_point_left_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_point_left_tangent #-}

instance Method "set_point_left_tangent" GodotCurve
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_point_left_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_point_right_tangent
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_point_right_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_point_right_tangent #-}

instance Method "set_point_right_tangent" GodotCurve
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_point_right_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_point_left_mode
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_point_left_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_point_left_mode #-}

instance Method "set_point_left_mode" GodotCurve
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_point_left_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_point_right_mode
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_point_right_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_point_right_mode #-}

instance Method "set_point_right_mode" GodotCurve
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_point_right_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_min_value
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_min_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_min_value #-}

instance Method "get_min_value" GodotCurve (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_min_value (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_min_value
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_min_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_min_value #-}

instance Method "set_min_value" GodotCurve (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_min_value (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_max_value
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_max_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_max_value #-}

instance Method "get_max_value" GodotCurve (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_max_value (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_max_value
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_max_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_max_value #-}

instance Method "set_max_value" GodotCurve (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_max_value (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_clean_dupes
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "clean_dupes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_clean_dupes #-}

instance Method "clean_dupes" GodotCurve (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_clean_dupes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_bake
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "bake" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_bake #-}

instance Method "bake" GodotCurve (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_bake (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_get_bake_resolution
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "get_bake_resolution" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_get_bake_resolution #-}

instance Method "get_bake_resolution" GodotCurve (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_get_bake_resolution (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve_set_bake_resolution
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "set_bake_resolution" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve_set_bake_resolution #-}

instance Method "set_bake_resolution" GodotCurve (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve_set_bake_resolution (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve__get_data
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve__get_data #-}

instance Method "_get_data" GodotCurve (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve__get_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve__set_data
  = unsafePerformIO $
      withCString "Curve" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve__set_data #-}

instance Method "_set_data" GodotCurve (GodotArray -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve__set_data (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGradientTexture = GodotGradientTexture GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotGradientTexture where
        type BaseClass GodotGradientTexture = GodotTexture
        super = coerce
bindGradientTexture_get_width
  = unsafePerformIO $
      withCString "GradientTexture" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradientTexture_get_width #-}

instance Method "get_width" GodotGradientTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradientTexture_get_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradientTexture_set_gradient
  = unsafePerformIO $
      withCString "GradientTexture" $
        \ clsNamePtr ->
          withCString "set_gradient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradientTexture_set_gradient #-}

instance Method "set_gradient" GodotGradientTexture
           (GodotGradient -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradientTexture_set_gradient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradientTexture_get_gradient
  = unsafePerformIO $
      withCString "GradientTexture" $
        \ clsNamePtr ->
          withCString "get_gradient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradientTexture_get_gradient #-}

instance Method "get_gradient" GodotGradientTexture
           (IO GodotGradient)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradientTexture_get_gradient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradientTexture_set_width
  = unsafePerformIO $
      withCString "GradientTexture" $
        \ clsNamePtr ->
          withCString "set_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradientTexture_set_width #-}

instance Method "set_width" GodotGradientTexture (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradientTexture_set_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradientTexture__update
  = unsafePerformIO $
      withCString "GradientTexture" $
        \ clsNamePtr ->
          withCString "_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradientTexture__update #-}

instance Method "_update" GodotGradientTexture (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradientTexture__update (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPosition3D = GodotPosition3D GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotPosition3D where
        type BaseClass GodotPosition3D = GodotSpatial
        super = coerce

newtype GodotNavigationMeshInstance = GodotNavigationMeshInstance GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotNavigationMeshInstance where
        type BaseClass GodotNavigationMeshInstance = GodotSpatial
        super = coerce
bindNavigationMeshInstance_set_navigation_mesh
  = unsafePerformIO $
      withCString "NavigationMeshInstance" $
        \ clsNamePtr ->
          withCString "set_navigation_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMeshInstance_set_navigation_mesh #-}

instance Method "set_navigation_mesh" GodotNavigationMeshInstance
           (GodotNavigationMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMeshInstance_set_navigation_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMeshInstance_get_navigation_mesh
  = unsafePerformIO $
      withCString "NavigationMeshInstance" $
        \ clsNamePtr ->
          withCString "get_navigation_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMeshInstance_get_navigation_mesh #-}

instance Method "get_navigation_mesh" GodotNavigationMeshInstance
           (IO GodotNavigationMesh)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMeshInstance_get_navigation_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMeshInstance_set_enabled
  = unsafePerformIO $
      withCString "NavigationMeshInstance" $
        \ clsNamePtr ->
          withCString "set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMeshInstance_set_enabled #-}

instance Method "set_enabled" GodotNavigationMeshInstance
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMeshInstance_set_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMeshInstance_is_enabled
  = unsafePerformIO $
      withCString "NavigationMeshInstance" $
        \ clsNamePtr ->
          withCString "is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMeshInstance_is_enabled #-}

instance Method "is_enabled" GodotNavigationMeshInstance (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMeshInstance_is_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNavigationMesh = GodotNavigationMesh GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotNavigationMesh where
        type BaseClass GodotNavigationMesh = GodotResource
        super = coerce
bindNavigationMesh_set_sample_partition_type
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_sample_partition_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_sample_partition_type #-}

instance Method "set_sample_partition_type" GodotNavigationMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_sample_partition_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_sample_partition_type
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_sample_partition_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_sample_partition_type #-}

instance Method "get_sample_partition_type" GodotNavigationMesh
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_sample_partition_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_cell_size
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_cell_size #-}

instance Method "set_cell_size" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_cell_size
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_cell_size #-}

instance Method "get_cell_size" GodotNavigationMesh (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_cell_height
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_cell_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_cell_height #-}

instance Method "set_cell_height" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_cell_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_cell_height
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_cell_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_cell_height #-}

instance Method "get_cell_height" GodotNavigationMesh (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_cell_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_agent_height
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_agent_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_agent_height #-}

instance Method "set_agent_height" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_agent_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_agent_height
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_agent_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_agent_height #-}

instance Method "get_agent_height" GodotNavigationMesh (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_agent_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_agent_radius
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_agent_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_agent_radius #-}

instance Method "set_agent_radius" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_agent_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_agent_radius
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_agent_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_agent_radius #-}

instance Method "get_agent_radius" GodotNavigationMesh (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_agent_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_agent_max_climb
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_agent_max_climb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_agent_max_climb #-}

instance Method "set_agent_max_climb" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_agent_max_climb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_agent_max_climb
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_agent_max_climb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_agent_max_climb #-}

instance Method "get_agent_max_climb" GodotNavigationMesh
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_agent_max_climb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_agent_max_slope
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_agent_max_slope" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_agent_max_slope #-}

instance Method "set_agent_max_slope" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_agent_max_slope
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_agent_max_slope
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_agent_max_slope" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_agent_max_slope #-}

instance Method "get_agent_max_slope" GodotNavigationMesh
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_agent_max_slope
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_region_min_size
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_region_min_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_region_min_size #-}

instance Method "set_region_min_size" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_region_min_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_region_min_size
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_region_min_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_region_min_size #-}

instance Method "get_region_min_size" GodotNavigationMesh
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_region_min_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_region_merge_size
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_region_merge_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_region_merge_size #-}

instance Method "set_region_merge_size" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_region_merge_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_region_merge_size
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_region_merge_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_region_merge_size #-}

instance Method "get_region_merge_size" GodotNavigationMesh
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_region_merge_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_edge_max_length
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_edge_max_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_edge_max_length #-}

instance Method "set_edge_max_length" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_edge_max_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_edge_max_length
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_edge_max_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_edge_max_length #-}

instance Method "get_edge_max_length" GodotNavigationMesh
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_edge_max_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_edge_max_error
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_edge_max_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_edge_max_error #-}

instance Method "set_edge_max_error" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_edge_max_error
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_edge_max_error
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_edge_max_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_edge_max_error #-}

instance Method "get_edge_max_error" GodotNavigationMesh (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_edge_max_error
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_verts_per_poly
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_verts_per_poly" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_verts_per_poly #-}

instance Method "set_verts_per_poly" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_verts_per_poly
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_verts_per_poly
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_verts_per_poly" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_verts_per_poly #-}

instance Method "get_verts_per_poly" GodotNavigationMesh (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_verts_per_poly
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_detail_sample_distance
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_detail_sample_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_detail_sample_distance #-}

instance Method "set_detail_sample_distance" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_set_detail_sample_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_detail_sample_distance
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_detail_sample_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_detail_sample_distance #-}

instance Method "get_detail_sample_distance" GodotNavigationMesh
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_get_detail_sample_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_detail_sample_max_error
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_detail_sample_max_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_detail_sample_max_error #-}

instance Method "set_detail_sample_max_error" GodotNavigationMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_set_detail_sample_max_error
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_detail_sample_max_error
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_detail_sample_max_error" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_detail_sample_max_error #-}

instance Method "get_detail_sample_max_error" GodotNavigationMesh
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_get_detail_sample_max_error
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_filter_low_hanging_obstacles
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_filter_low_hanging_obstacles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_filter_low_hanging_obstacles
             #-}

instance Method "set_filter_low_hanging_obstacles"
           GodotNavigationMesh
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_set_filter_low_hanging_obstacles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_filter_low_hanging_obstacles
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_filter_low_hanging_obstacles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_filter_low_hanging_obstacles
             #-}

instance Method "get_filter_low_hanging_obstacles"
           GodotNavigationMesh
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_get_filter_low_hanging_obstacles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_filter_ledge_spans
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_filter_ledge_spans" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_filter_ledge_spans #-}

instance Method "set_filter_ledge_spans" GodotNavigationMesh
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_filter_ledge_spans
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_filter_ledge_spans
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_filter_ledge_spans" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_filter_ledge_spans #-}

instance Method "get_filter_ledge_spans" GodotNavigationMesh
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_filter_ledge_spans
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_filter_walkable_low_height_spans
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_filter_walkable_low_height_spans" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_filter_walkable_low_height_spans
             #-}

instance Method "set_filter_walkable_low_height_spans"
           GodotNavigationMesh
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_set_filter_walkable_low_height_spans
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_filter_walkable_low_height_spans
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_filter_walkable_low_height_spans" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_filter_walkable_low_height_spans
             #-}

instance Method "get_filter_walkable_low_height_spans"
           GodotNavigationMesh
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationMesh_get_filter_walkable_low_height_spans
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_set_vertices
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "set_vertices" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_set_vertices #-}

instance Method "set_vertices" GodotNavigationMesh
           (GodotPoolVector3Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_set_vertices (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_vertices
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_vertices" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_vertices #-}

instance Method "get_vertices" GodotNavigationMesh
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_vertices (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_add_polygon
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "add_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_add_polygon #-}

instance Method "add_polygon" GodotNavigationMesh
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_add_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_polygon_count
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_polygon_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_polygon_count #-}

instance Method "get_polygon_count" GodotNavigationMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_polygon_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_get_polygon
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "get_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_get_polygon #-}

instance Method "get_polygon" GodotNavigationMesh
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_get_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_clear_polygons
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "clear_polygons" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_clear_polygons #-}

instance Method "clear_polygons" GodotNavigationMesh (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_clear_polygons
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh_create_from_mesh
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "create_from_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh_create_from_mesh #-}

instance Method "create_from_mesh" GodotNavigationMesh
           (GodotMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh_create_from_mesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh__set_polygons
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "_set_polygons" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh__set_polygons #-}

instance Method "_set_polygons" GodotNavigationMesh
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh__set_polygons
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationMesh__get_polygons
  = unsafePerformIO $
      withCString "NavigationMesh" $
        \ clsNamePtr ->
          withCString "_get_polygons" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationMesh__get_polygons #-}

instance Method "_get_polygons" GodotNavigationMesh (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationMesh__get_polygons
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNavigation = GodotNavigation GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotNavigation where
        type BaseClass GodotNavigation = GodotSpatial
        super = coerce
bindNavigation_navmesh_add
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "navmesh_add" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_navmesh_add #-}

instance Method "navmesh_add" GodotNavigation
           (GodotNavigationMesh -> GodotTransform -> GodotObject -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_navmesh_add (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_navmesh_set_transform
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "navmesh_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_navmesh_set_transform #-}

instance Method "navmesh_set_transform" GodotNavigation
           (Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_navmesh_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_navmesh_remove
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "navmesh_remove" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_navmesh_remove #-}

instance Method "navmesh_remove" GodotNavigation (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_navmesh_remove (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_get_simple_path
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "get_simple_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_get_simple_path #-}

instance Method "get_simple_path" GodotNavigation
           (GodotVector3 -> GodotVector3 -> Bool -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_get_simple_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_get_closest_point_to_segment
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "get_closest_point_to_segment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_get_closest_point_to_segment #-}

instance Method "get_closest_point_to_segment" GodotNavigation
           (GodotVector3 -> GodotVector3 -> Bool -> IO GodotVector3)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_get_closest_point_to_segment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_get_closest_point
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "get_closest_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_get_closest_point #-}

instance Method "get_closest_point" GodotNavigation
           (GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_get_closest_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_get_closest_point_normal
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "get_closest_point_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_get_closest_point_normal #-}

instance Method "get_closest_point_normal" GodotNavigation
           (GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_get_closest_point_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_get_closest_point_owner
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "get_closest_point_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_get_closest_point_owner #-}

instance Method "get_closest_point_owner" GodotNavigation
           (GodotVector3 -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_get_closest_point_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_set_up_vector
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "set_up_vector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_set_up_vector #-}

instance Method "set_up_vector" GodotNavigation
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_set_up_vector (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation_get_up_vector
  = unsafePerformIO $
      withCString "Navigation" $
        \ clsNamePtr ->
          withCString "get_up_vector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation_get_up_vector #-}

instance Method "get_up_vector" GodotNavigation (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation_get_up_vector (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRootMotionView = GodotRootMotionView GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotRootMotionView where
        type BaseClass GodotRootMotionView = GodotVisualInstance
        super = coerce
bindRootMotionView_get_animation_path
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "get_animation_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_get_animation_path #-}

instance Method "get_animation_path" GodotRootMotionView
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_get_animation_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_set_animation_path
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "set_animation_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_set_animation_path #-}

instance Method "set_animation_path" GodotRootMotionView
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_set_animation_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_get_color
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_get_color #-}

instance Method "get_color" GodotRootMotionView (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_get_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_set_color
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_set_color #-}

instance Method "set_color" GodotRootMotionView
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_set_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_get_cell_size
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "get_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_get_cell_size #-}

instance Method "get_cell_size" GodotRootMotionView (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_get_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_set_cell_size
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "set_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_set_cell_size #-}

instance Method "set_cell_size" GodotRootMotionView
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_set_cell_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_get_radius
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_get_radius #-}

instance Method "get_radius" GodotRootMotionView (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_set_radius
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_set_radius #-}

instance Method "set_radius" GodotRootMotionView (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_get_zero_y
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "get_zero_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_get_zero_y #-}

instance Method "get_zero_y" GodotRootMotionView (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_get_zero_y (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRootMotionView_set_zero_y
  = unsafePerformIO $
      withCString "RootMotionView" $
        \ clsNamePtr ->
          withCString "set_zero_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRootMotionView_set_zero_y #-}

instance Method "set_zero_y" GodotRootMotionView (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRootMotionView_set_zero_y (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationTree = GodotAnimationTree GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotAnimationTree where
        type BaseClass GodotAnimationTree = GodotNode
        super = coerce
bindAnimationTree_set_active
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "set_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_set_active #-}

instance Method "set_active" GodotAnimationTree (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_set_active (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_is_active
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_is_active #-}

instance Method "is_active" GodotAnimationTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_is_active (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_set_tree_root
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "set_tree_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_set_tree_root #-}

instance Method "set_tree_root" GodotAnimationTree
           (GodotAnimationNode -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_set_tree_root (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_get_tree_root
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "get_tree_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_get_tree_root #-}

instance Method "get_tree_root" GodotAnimationTree
           (IO GodotAnimationNode)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_get_tree_root (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_set_process_mode
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "set_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_set_process_mode #-}

instance Method "set_process_mode" GodotAnimationTree
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_set_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_get_process_mode
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "get_process_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_get_process_mode #-}

instance Method "get_process_mode" GodotAnimationTree (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_get_process_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_set_animation_player
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "set_animation_player" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_set_animation_player #-}

instance Method "set_animation_player" GodotAnimationTree
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_set_animation_player
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_get_animation_player
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "get_animation_player" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_get_animation_player #-}

instance Method "get_animation_player" GodotAnimationTree
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_get_animation_player
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_set_root_motion_track
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "set_root_motion_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_set_root_motion_track #-}

instance Method "set_root_motion_track" GodotAnimationTree
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_set_root_motion_track
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_get_root_motion_track
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "get_root_motion_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_get_root_motion_track #-}

instance Method "get_root_motion_track" GodotAnimationTree
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_get_root_motion_track
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_get_root_motion_transform
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "get_root_motion_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_get_root_motion_transform #-}

instance Method "get_root_motion_transform" GodotAnimationTree
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_get_root_motion_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree__tree_changed
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "_tree_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree__tree_changed #-}

instance Method "_tree_changed" GodotAnimationTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree__tree_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree__update_properties
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "_update_properties" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree__update_properties #-}

instance Method "_update_properties" GodotAnimationTree (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree__update_properties
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_rename_parameter
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "rename_parameter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_rename_parameter #-}

instance Method "rename_parameter" GodotAnimationTree
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_rename_parameter
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree_advance
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree_advance #-}

instance Method "advance" GodotAnimationTree (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree_advance (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree__node_removed
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "_node_removed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree__node_removed #-}

instance Method "_node_removed" GodotAnimationTree
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree__node_removed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationTree__clear_caches
  = unsafePerformIO $
      withCString "AnimationTree" $
        \ clsNamePtr ->
          withCString "_clear_caches" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationTree__clear_caches #-}

instance Method "_clear_caches" GodotAnimationTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationTree__clear_caches (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationRootNode = GodotAnimationRootNode GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAnimationRootNode where
        type BaseClass GodotAnimationRootNode = GodotAnimationNode
        super = coerce

newtype GodotAnimationNode = GodotAnimationNode GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotAnimationNode where
        type BaseClass GodotAnimationNode = GodotResource
        super = coerce
bindAnimationNode_process
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "process" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_process #-}

instance Method "process" GodotAnimationNode
           (Float -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_process (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_get_caption
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "get_caption" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_get_caption #-}

instance Method "get_caption" GodotAnimationNode (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_get_caption (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_has_filter
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "has_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_has_filter #-}

instance Method "has_filter" GodotAnimationNode (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_has_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_get_input_count
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "get_input_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_get_input_count #-}

instance Method "get_input_count" GodotAnimationNode (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_get_input_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_get_input_name
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "get_input_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_get_input_name #-}

instance Method "get_input_name" GodotAnimationNode
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_get_input_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_add_input
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "add_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_add_input #-}

instance Method "add_input" GodotAnimationNode
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_add_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_remove_input
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "remove_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_remove_input #-}

instance Method "remove_input" GodotAnimationNode (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_remove_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_set_filter_path
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "set_filter_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_set_filter_path #-}

instance Method "set_filter_path" GodotAnimationNode
           (GodotNodePath -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_set_filter_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_is_path_filtered
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "is_path_filtered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_is_path_filtered #-}

instance Method "is_path_filtered" GodotAnimationNode
           (GodotNodePath -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_is_path_filtered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_set_filter_enabled
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "set_filter_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_set_filter_enabled #-}

instance Method "set_filter_enabled" GodotAnimationNode
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_set_filter_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_is_filter_enabled
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "is_filter_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_is_filter_enabled #-}

instance Method "is_filter_enabled" GodotAnimationNode (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_is_filter_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode__set_filters
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "_set_filters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode__set_filters #-}

instance Method "_set_filters" GodotAnimationNode
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode__set_filters (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode__get_filters
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "_get_filters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode__get_filters #-}

instance Method "_get_filters" GodotAnimationNode (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode__get_filters (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_blend_animation
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "blend_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_blend_animation #-}

instance Method "blend_animation" GodotAnimationNode
           (GodotString -> Float -> Float -> Bool -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_blend_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_blend_node
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "blend_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_blend_node #-}

instance Method "blend_node" GodotAnimationNode
           (GodotString ->
              GodotAnimationNode ->
                Float -> Bool -> Float -> Int -> Bool -> IO Float)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_blend_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_blend_input
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "blend_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_blend_input #-}

instance Method "blend_input" GodotAnimationNode
           (Int -> Float -> Bool -> Float -> Int -> Bool -> IO Float)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_blend_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_set_parameter
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "set_parameter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_set_parameter #-}

instance Method "set_parameter" GodotAnimationNode
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_set_parameter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNode_get_parameter
  = unsafePerformIO $
      withCString "AnimationNode" $
        \ clsNamePtr ->
          withCString "get_parameter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNode_get_parameter #-}

instance Method "get_parameter" GodotAnimationNode
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNode_get_parameter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeBlendTree = GodotAnimationNodeBlendTree GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeBlendTree where
        type BaseClass GodotAnimationNodeBlendTree = GodotAnimationRootNode
        super = coerce
bindAnimationNodeBlendTree_add_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "add_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_add_node #-}

instance Method "add_node" GodotAnimationNodeBlendTree
           (GodotString -> GodotAnimationNode -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_add_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_get_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "get_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_get_node #-}

instance Method "get_node" GodotAnimationNodeBlendTree
           (GodotString -> IO GodotAnimationNode)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_get_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_remove_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "remove_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_remove_node #-}

instance Method "remove_node" GodotAnimationNodeBlendTree
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_remove_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_rename_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "rename_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_rename_node #-}

instance Method "rename_node" GodotAnimationNodeBlendTree
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_rename_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_has_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "has_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_has_node #-}

instance Method "has_node" GodotAnimationNodeBlendTree
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_has_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_connect_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "connect_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_connect_node #-}

instance Method "connect_node" GodotAnimationNodeBlendTree
           (GodotString -> Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_connect_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_disconnect_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "disconnect_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_disconnect_node #-}

instance Method "disconnect_node" GodotAnimationNodeBlendTree
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_disconnect_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_set_node_position
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "set_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_set_node_position #-}

instance Method "set_node_position" GodotAnimationNodeBlendTree
           (GodotString -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_set_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_get_node_position
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "get_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_get_node_position #-}

instance Method "get_node_position" GodotAnimationNodeBlendTree
           (GodotString -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_get_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_set_graph_offset
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "set_graph_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_set_graph_offset #-}

instance Method "set_graph_offset" GodotAnimationNodeBlendTree
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_set_graph_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree_get_graph_offset
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "get_graph_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree_get_graph_offset #-}

instance Method "get_graph_offset" GodotAnimationNodeBlendTree
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree_get_graph_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree__tree_changed
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "_tree_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree__tree_changed #-}

instance Method "_tree_changed" GodotAnimationNodeBlendTree (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree__tree_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendTree__node_changed
  = unsafePerformIO $
      withCString "AnimationNodeBlendTree" $
        \ clsNamePtr ->
          withCString "_node_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendTree__node_changed #-}

instance Method "_node_changed" GodotAnimationNodeBlendTree
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendTree__node_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeBlendSpace1D = GodotAnimationNodeBlendSpace1D GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeBlendSpace1D where
        type BaseClass GodotAnimationNodeBlendSpace1D =
             GodotAnimationRootNode
        super = coerce
bindAnimationNodeBlendSpace1D_add_blend_point
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "add_blend_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_add_blend_point #-}

instance Method "add_blend_point" GodotAnimationNodeBlendSpace1D
           (GodotAnimationRootNode -> Float -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_add_blend_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_set_blend_point_position
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "set_blend_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_set_blend_point_position
             #-}

instance Method "set_blend_point_position"
           GodotAnimationNodeBlendSpace1D
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_set_blend_point_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_get_blend_point_position
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "get_blend_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_get_blend_point_position
             #-}

instance Method "get_blend_point_position"
           GodotAnimationNodeBlendSpace1D
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_get_blend_point_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_set_blend_point_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "set_blend_point_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_set_blend_point_node #-}

instance Method "set_blend_point_node"
           GodotAnimationNodeBlendSpace1D
           (Int -> GodotAnimationRootNode -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_set_blend_point_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_get_blend_point_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "get_blend_point_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_get_blend_point_node #-}

instance Method "get_blend_point_node"
           GodotAnimationNodeBlendSpace1D
           (Int -> IO GodotAnimationRootNode)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_get_blend_point_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_remove_blend_point
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "remove_blend_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_remove_blend_point #-}

instance Method "remove_blend_point" GodotAnimationNodeBlendSpace1D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_remove_blend_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_get_blend_point_count
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "get_blend_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_get_blend_point_count
             #-}

instance Method "get_blend_point_count"
           GodotAnimationNodeBlendSpace1D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_get_blend_point_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_set_min_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "set_min_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_set_min_space #-}

instance Method "set_min_space" GodotAnimationNodeBlendSpace1D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace1D_set_min_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_get_min_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "get_min_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_get_min_space #-}

instance Method "get_min_space" GodotAnimationNodeBlendSpace1D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace1D_get_min_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_set_max_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "set_max_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_set_max_space #-}

instance Method "set_max_space" GodotAnimationNodeBlendSpace1D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace1D_set_max_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_get_max_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "get_max_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_get_max_space #-}

instance Method "get_max_space" GodotAnimationNodeBlendSpace1D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace1D_get_max_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_set_snap
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "set_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_set_snap #-}

instance Method "set_snap" GodotAnimationNodeBlendSpace1D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace1D_set_snap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_get_snap
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "get_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_get_snap #-}

instance Method "get_snap" GodotAnimationNodeBlendSpace1D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace1D_get_snap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_set_value_label
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "set_value_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_set_value_label #-}

instance Method "set_value_label" GodotAnimationNodeBlendSpace1D
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_set_value_label
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D_get_value_label
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "get_value_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D_get_value_label #-}

instance Method "get_value_label" GodotAnimationNodeBlendSpace1D
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D_get_value_label
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D__add_blend_point
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "_add_blend_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D__add_blend_point #-}

instance Method "_add_blend_point" GodotAnimationNodeBlendSpace1D
           (Int -> GodotAnimationRootNode -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace1D__add_blend_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace1D__tree_changed
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace1D" $
        \ clsNamePtr ->
          withCString "_tree_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace1D__tree_changed #-}

instance Method "_tree_changed" GodotAnimationNodeBlendSpace1D
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace1D__tree_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeBlendSpace2D = GodotAnimationNodeBlendSpace2D GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeBlendSpace2D where
        type BaseClass GodotAnimationNodeBlendSpace2D =
             GodotAnimationRootNode
        super = coerce
bindAnimationNodeBlendSpace2D_add_blend_point
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "add_blend_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_add_blend_point #-}

instance Method "add_blend_point" GodotAnimationNodeBlendSpace2D
           (GodotAnimationRootNode -> GodotVector2 -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_add_blend_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_blend_point_position
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_blend_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_blend_point_position
             #-}

instance Method "set_blend_point_position"
           GodotAnimationNodeBlendSpace2D
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_set_blend_point_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_blend_point_position
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_blend_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_blend_point_position
             #-}

instance Method "get_blend_point_position"
           GodotAnimationNodeBlendSpace2D
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_get_blend_point_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_blend_point_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_blend_point_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_blend_point_node #-}

instance Method "set_blend_point_node"
           GodotAnimationNodeBlendSpace2D
           (Int -> GodotAnimationRootNode -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_set_blend_point_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_blend_point_node
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_blend_point_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_blend_point_node #-}

instance Method "get_blend_point_node"
           GodotAnimationNodeBlendSpace2D
           (Int -> IO GodotAnimationRootNode)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_get_blend_point_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_remove_blend_point
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "remove_blend_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_remove_blend_point #-}

instance Method "remove_blend_point" GodotAnimationNodeBlendSpace2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_remove_blend_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_blend_point_count
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_blend_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_blend_point_count
             #-}

instance Method "get_blend_point_count"
           GodotAnimationNodeBlendSpace2D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_get_blend_point_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_add_triangle
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "add_triangle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_add_triangle #-}

instance Method "add_triangle" GodotAnimationNodeBlendSpace2D
           (Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_add_triangle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_triangle_point
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_triangle_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_triangle_point #-}

instance Method "get_triangle_point" GodotAnimationNodeBlendSpace2D
           (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_get_triangle_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_remove_triangle
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "remove_triangle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_remove_triangle #-}

instance Method "remove_triangle" GodotAnimationNodeBlendSpace2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_remove_triangle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_triangle_count
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_triangle_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_triangle_count #-}

instance Method "get_triangle_count" GodotAnimationNodeBlendSpace2D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_get_triangle_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_min_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_min_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_min_space #-}

instance Method "set_min_space" GodotAnimationNodeBlendSpace2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_set_min_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_min_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_min_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_min_space #-}

instance Method "get_min_space" GodotAnimationNodeBlendSpace2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_get_min_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_max_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_max_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_max_space #-}

instance Method "set_max_space" GodotAnimationNodeBlendSpace2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_set_max_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_max_space
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_max_space" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_max_space #-}

instance Method "get_max_space" GodotAnimationNodeBlendSpace2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_get_max_space
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_snap
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_snap #-}

instance Method "set_snap" GodotAnimationNodeBlendSpace2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_set_snap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_snap
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_snap #-}

instance Method "get_snap" GodotAnimationNodeBlendSpace2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_get_snap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_x_label
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_x_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_x_label #-}

instance Method "set_x_label" GodotAnimationNodeBlendSpace2D
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_set_x_label
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_x_label
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_x_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_x_label #-}

instance Method "get_x_label" GodotAnimationNodeBlendSpace2D
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_get_x_label
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_y_label
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_y_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_y_label #-}

instance Method "set_y_label" GodotAnimationNodeBlendSpace2D
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_set_y_label
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_y_label
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_y_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_y_label #-}

instance Method "get_y_label" GodotAnimationNodeBlendSpace2D
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D_get_y_label
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D__add_blend_point
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "_add_blend_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D__add_blend_point #-}

instance Method "_add_blend_point" GodotAnimationNodeBlendSpace2D
           (Int -> GodotAnimationRootNode -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D__add_blend_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D__set_triangles
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "_set_triangles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D__set_triangles #-}

instance Method "_set_triangles" GodotAnimationNodeBlendSpace2D
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D__set_triangles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D__get_triangles
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "_get_triangles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D__get_triangles #-}

instance Method "_get_triangles" GodotAnimationNodeBlendSpace2D
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D__get_triangles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_set_auto_triangles
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "set_auto_triangles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_set_auto_triangles #-}

instance Method "set_auto_triangles" GodotAnimationNodeBlendSpace2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_set_auto_triangles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D_get_auto_triangles
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "get_auto_triangles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D_get_auto_triangles #-}

instance Method "get_auto_triangles" GodotAnimationNodeBlendSpace2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeBlendSpace2D_get_auto_triangles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlendSpace2D__tree_changed
  = unsafePerformIO $
      withCString "AnimationNodeBlendSpace2D" $
        \ clsNamePtr ->
          withCString "_tree_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlendSpace2D__tree_changed #-}

instance Method "_tree_changed" GodotAnimationNodeBlendSpace2D
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlendSpace2D__tree_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeStateMachine = GodotAnimationNodeStateMachine GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeStateMachine where
        type BaseClass GodotAnimationNodeStateMachine =
             GodotAnimationRootNode
        super = coerce
bindAnimationNodeStateMachine_add_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "add_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_add_node #-}

instance Method "add_node" GodotAnimationNodeStateMachine
           (GodotString -> GodotAnimationNode -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_add_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_node #-}

instance Method "get_node" GodotAnimationNodeStateMachine
           (GodotString -> IO GodotAnimationNode)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_get_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_remove_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "remove_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_remove_node #-}

instance Method "remove_node" GodotAnimationNodeStateMachine
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_remove_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_rename_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "rename_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_rename_node #-}

instance Method "rename_node" GodotAnimationNodeStateMachine
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_rename_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_has_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "has_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_has_node #-}

instance Method "has_node" GodotAnimationNodeStateMachine
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_has_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_node_name
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_node_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_node_name #-}

instance Method "get_node_name" GodotAnimationNodeStateMachine
           (GodotAnimationNode -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_get_node_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_set_node_position
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "set_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_set_node_position #-}

instance Method "set_node_position" GodotAnimationNodeStateMachine
           (GodotString -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_set_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_node_position
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_node_position #-}

instance Method "get_node_position" GodotAnimationNodeStateMachine
           (GodotString -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_get_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_has_transition
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "has_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_has_transition #-}

instance Method "has_transition" GodotAnimationNodeStateMachine
           (GodotString -> GodotString -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_has_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_add_transition
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "add_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_add_transition #-}

instance Method "add_transition" GodotAnimationNodeStateMachine
           (GodotString ->
              GodotString -> GodotAnimationNodeStateMachineTransition -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_add_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_transition
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_transition #-}

instance Method "get_transition" GodotAnimationNodeStateMachine
           (Int -> IO GodotAnimationNodeStateMachineTransition)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_get_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_transition_from
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_transition_from" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_transition_from #-}

instance Method "get_transition_from"
           GodotAnimationNodeStateMachine
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_get_transition_from
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_transition_to
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_transition_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_transition_to #-}

instance Method "get_transition_to" GodotAnimationNodeStateMachine
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_get_transition_to
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_transition_count
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_transition_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_transition_count #-}

instance Method "get_transition_count"
           GodotAnimationNodeStateMachine
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_get_transition_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_remove_transition_by_index
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "remove_transition_by_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_remove_transition_by_index
             #-}

instance Method "remove_transition_by_index"
           GodotAnimationNodeStateMachine
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_remove_transition_by_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_remove_transition
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "remove_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_remove_transition #-}

instance Method "remove_transition" GodotAnimationNodeStateMachine
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_remove_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_set_start_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "set_start_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_set_start_node #-}

instance Method "set_start_node" GodotAnimationNodeStateMachine
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_set_start_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_start_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_start_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_start_node #-}

instance Method "get_start_node" GodotAnimationNodeStateMachine
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_get_start_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_set_end_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "set_end_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_set_end_node #-}

instance Method "set_end_node" GodotAnimationNodeStateMachine
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_set_end_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_end_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_end_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_end_node #-}

instance Method "get_end_node" GodotAnimationNodeStateMachine
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine_get_end_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_set_graph_offset
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "set_graph_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_set_graph_offset #-}

instance Method "set_graph_offset" GodotAnimationNodeStateMachine
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_set_graph_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine_get_graph_offset
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "get_graph_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine_get_graph_offset #-}

instance Method "get_graph_offset" GodotAnimationNodeStateMachine
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachine_get_graph_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachine__tree_changed
  = unsafePerformIO $
      withCString "AnimationNodeStateMachine" $
        \ clsNamePtr ->
          withCString "_tree_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachine__tree_changed #-}

instance Method "_tree_changed" GodotAnimationNodeStateMachine
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachine__tree_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeStateMachinePlayback = GodotAnimationNodeStateMachinePlayback GodotObject
                                                   deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeStateMachinePlayback where
        type BaseClass GodotAnimationNodeStateMachinePlayback =
             GodotResource
        super = coerce
bindAnimationNodeStateMachinePlayback_travel
  = unsafePerformIO $
      withCString "AnimationNodeStateMachinePlayback" $
        \ clsNamePtr ->
          withCString "travel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachinePlayback_travel #-}

instance Method "travel" GodotAnimationNodeStateMachinePlayback
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachinePlayback_travel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachinePlayback_start
  = unsafePerformIO $
      withCString "AnimationNodeStateMachinePlayback" $
        \ clsNamePtr ->
          withCString "start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachinePlayback_start #-}

instance Method "start" GodotAnimationNodeStateMachinePlayback
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachinePlayback_start
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachinePlayback_stop
  = unsafePerformIO $
      withCString "AnimationNodeStateMachinePlayback" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachinePlayback_stop #-}

instance Method "stop" GodotAnimationNodeStateMachinePlayback
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeStateMachinePlayback_stop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachinePlayback_is_playing
  = unsafePerformIO $
      withCString "AnimationNodeStateMachinePlayback" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachinePlayback_is_playing #-}

instance Method "is_playing" GodotAnimationNodeStateMachinePlayback
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachinePlayback_is_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachinePlayback_get_current_node
  = unsafePerformIO $
      withCString "AnimationNodeStateMachinePlayback" $
        \ clsNamePtr ->
          withCString "get_current_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachinePlayback_get_current_node
             #-}

instance Method "get_current_node"
           GodotAnimationNodeStateMachinePlayback
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachinePlayback_get_current_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachinePlayback_get_travel_path
  = unsafePerformIO $
      withCString "AnimationNodeStateMachinePlayback" $
        \ clsNamePtr ->
          withCString "get_travel_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachinePlayback_get_travel_path
             #-}

instance Method "get_travel_path"
           GodotAnimationNodeStateMachinePlayback
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachinePlayback_get_travel_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeStateMachineTransition = GodotAnimationNodeStateMachineTransition GodotObject
                                                     deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeStateMachineTransition
         where
        type BaseClass GodotAnimationNodeStateMachineTransition =
             GodotResource
        super = coerce
bindAnimationNodeStateMachineTransition_set_switch_mode
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "set_switch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_set_switch_mode
             #-}

instance Method "set_switch_mode"
           GodotAnimationNodeStateMachineTransition
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_set_switch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_get_switch_mode
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "get_switch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_get_switch_mode
             #-}

instance Method "get_switch_mode"
           GodotAnimationNodeStateMachineTransition
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_get_switch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_set_auto_advance
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "set_auto_advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_set_auto_advance
             #-}

instance Method "set_auto_advance"
           GodotAnimationNodeStateMachineTransition
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_set_auto_advance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_has_auto_advance
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "has_auto_advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_has_auto_advance
             #-}

instance Method "has_auto_advance"
           GodotAnimationNodeStateMachineTransition
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_has_auto_advance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_set_advance_condition
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "set_advance_condition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_set_advance_condition
             #-}

instance Method "set_advance_condition"
           GodotAnimationNodeStateMachineTransition
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_set_advance_condition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_get_advance_condition
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "get_advance_condition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_get_advance_condition
             #-}

instance Method "get_advance_condition"
           GodotAnimationNodeStateMachineTransition
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_get_advance_condition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_set_xfade_time
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "set_xfade_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_set_xfade_time
             #-}

instance Method "set_xfade_time"
           GodotAnimationNodeStateMachineTransition
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_set_xfade_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_get_xfade_time
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "get_xfade_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_get_xfade_time
             #-}

instance Method "get_xfade_time"
           GodotAnimationNodeStateMachineTransition
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_get_xfade_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_set_disabled
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_set_disabled
             #-}

instance Method "set_disabled"
           GodotAnimationNodeStateMachineTransition
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_set_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_is_disabled
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "is_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_is_disabled
             #-}

instance Method "is_disabled"
           GodotAnimationNodeStateMachineTransition
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_is_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_set_priority
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "set_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_set_priority
             #-}

instance Method "set_priority"
           GodotAnimationNodeStateMachineTransition
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_set_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeStateMachineTransition_get_priority
  = unsafePerformIO $
      withCString "AnimationNodeStateMachineTransition" $
        \ clsNamePtr ->
          withCString "get_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeStateMachineTransition_get_priority
             #-}

instance Method "get_priority"
           GodotAnimationNodeStateMachineTransition
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeStateMachineTransition_get_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeOutput = GodotAnimationNodeOutput GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeOutput where
        type BaseClass GodotAnimationNodeOutput = GodotAnimationNode
        super = coerce

newtype GodotAnimationNodeOneShot = GodotAnimationNodeOneShot GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeOneShot where
        type BaseClass GodotAnimationNodeOneShot = GodotAnimationNode
        super = coerce
bindAnimationNodeOneShot_set_fadein_time
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "set_fadein_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_set_fadein_time #-}

instance Method "set_fadein_time" GodotAnimationNodeOneShot
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_set_fadein_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_get_fadein_time
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "get_fadein_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_get_fadein_time #-}

instance Method "get_fadein_time" GodotAnimationNodeOneShot
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_get_fadein_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_set_fadeout_time
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "set_fadeout_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_set_fadeout_time #-}

instance Method "set_fadeout_time" GodotAnimationNodeOneShot
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_set_fadeout_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_get_fadeout_time
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "get_fadeout_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_get_fadeout_time #-}

instance Method "get_fadeout_time" GodotAnimationNodeOneShot
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_get_fadeout_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_set_autorestart
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "set_autorestart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_set_autorestart #-}

instance Method "set_autorestart" GodotAnimationNodeOneShot
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_set_autorestart
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_has_autorestart
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "has_autorestart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_has_autorestart #-}

instance Method "has_autorestart" GodotAnimationNodeOneShot
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_has_autorestart
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_set_autorestart_delay
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "set_autorestart_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_set_autorestart_delay #-}

instance Method "set_autorestart_delay" GodotAnimationNodeOneShot
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeOneShot_set_autorestart_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_get_autorestart_delay
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "get_autorestart_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_get_autorestart_delay #-}

instance Method "get_autorestart_delay" GodotAnimationNodeOneShot
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeOneShot_get_autorestart_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_set_autorestart_random_delay
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "set_autorestart_random_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_set_autorestart_random_delay
             #-}

instance Method "set_autorestart_random_delay"
           GodotAnimationNodeOneShot
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeOneShot_set_autorestart_random_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_get_autorestart_random_delay
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "get_autorestart_random_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_get_autorestart_random_delay
             #-}

instance Method "get_autorestart_random_delay"
           GodotAnimationNodeOneShot
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeOneShot_get_autorestart_random_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_set_mix_mode
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "set_mix_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_set_mix_mode #-}

instance Method "set_mix_mode" GodotAnimationNodeOneShot
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_set_mix_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_get_mix_mode
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "get_mix_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_get_mix_mode #-}

instance Method "get_mix_mode" GodotAnimationNodeOneShot (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_get_mix_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_set_use_sync
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "set_use_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_set_use_sync #-}

instance Method "set_use_sync" GodotAnimationNodeOneShot
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_set_use_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeOneShot_is_using_sync
  = unsafePerformIO $
      withCString "AnimationNodeOneShot" $
        \ clsNamePtr ->
          withCString "is_using_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeOneShot_is_using_sync #-}

instance Method "is_using_sync" GodotAnimationNodeOneShot (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeOneShot_is_using_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeAnimation = GodotAnimationNodeAnimation GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeAnimation where
        type BaseClass GodotAnimationNodeAnimation = GodotAnimationRootNode
        super = coerce
bindAnimationNodeAnimation_set_animation
  = unsafePerformIO $
      withCString "AnimationNodeAnimation" $
        \ clsNamePtr ->
          withCString "set_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeAnimation_set_animation #-}

instance Method "set_animation" GodotAnimationNodeAnimation
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeAnimation_set_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeAnimation_get_animation
  = unsafePerformIO $
      withCString "AnimationNodeAnimation" $
        \ clsNamePtr ->
          withCString "get_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeAnimation_get_animation #-}

instance Method "get_animation" GodotAnimationNodeAnimation
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeAnimation_get_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeAnimation_get_playback_time
  = unsafePerformIO $
      withCString "AnimationNodeAnimation" $
        \ clsNamePtr ->
          withCString "get_playback_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeAnimation_get_playback_time #-}

instance Method "get_playback_time" GodotAnimationNodeAnimation
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeAnimation_get_playback_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeAdd2 = GodotAnimationNodeAdd2 GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeAdd2 where
        type BaseClass GodotAnimationNodeAdd2 = GodotAnimationNode
        super = coerce
bindAnimationNodeAdd2_set_use_sync
  = unsafePerformIO $
      withCString "AnimationNodeAdd2" $
        \ clsNamePtr ->
          withCString "set_use_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeAdd2_set_use_sync #-}

instance Method "set_use_sync" GodotAnimationNodeAdd2
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeAdd2_set_use_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeAdd2_is_using_sync
  = unsafePerformIO $
      withCString "AnimationNodeAdd2" $
        \ clsNamePtr ->
          withCString "is_using_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeAdd2_is_using_sync #-}

instance Method "is_using_sync" GodotAnimationNodeAdd2 (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeAdd2_is_using_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeAdd3 = GodotAnimationNodeAdd3 GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeAdd3 where
        type BaseClass GodotAnimationNodeAdd3 = GodotAnimationNode
        super = coerce
bindAnimationNodeAdd3_set_use_sync
  = unsafePerformIO $
      withCString "AnimationNodeAdd3" $
        \ clsNamePtr ->
          withCString "set_use_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeAdd3_set_use_sync #-}

instance Method "set_use_sync" GodotAnimationNodeAdd3
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeAdd3_set_use_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeAdd3_is_using_sync
  = unsafePerformIO $
      withCString "AnimationNodeAdd3" $
        \ clsNamePtr ->
          withCString "is_using_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeAdd3_is_using_sync #-}

instance Method "is_using_sync" GodotAnimationNodeAdd3 (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeAdd3_is_using_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeBlend2 = GodotAnimationNodeBlend2 GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeBlend2 where
        type BaseClass GodotAnimationNodeBlend2 = GodotAnimationNode
        super = coerce
bindAnimationNodeBlend2_set_use_sync
  = unsafePerformIO $
      withCString "AnimationNodeBlend2" $
        \ clsNamePtr ->
          withCString "set_use_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlend2_set_use_sync #-}

instance Method "set_use_sync" GodotAnimationNodeBlend2
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlend2_set_use_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlend2_is_using_sync
  = unsafePerformIO $
      withCString "AnimationNodeBlend2" $
        \ clsNamePtr ->
          withCString "is_using_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlend2_is_using_sync #-}

instance Method "is_using_sync" GodotAnimationNodeBlend2 (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlend2_is_using_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeBlend3 = GodotAnimationNodeBlend3 GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeBlend3 where
        type BaseClass GodotAnimationNodeBlend3 = GodotAnimationNode
        super = coerce
bindAnimationNodeBlend3_set_use_sync
  = unsafePerformIO $
      withCString "AnimationNodeBlend3" $
        \ clsNamePtr ->
          withCString "set_use_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlend3_set_use_sync #-}

instance Method "set_use_sync" GodotAnimationNodeBlend3
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlend3_set_use_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeBlend3_is_using_sync
  = unsafePerformIO $
      withCString "AnimationNodeBlend3" $
        \ clsNamePtr ->
          withCString "is_using_sync" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeBlend3_is_using_sync #-}

instance Method "is_using_sync" GodotAnimationNodeBlend3 (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimationNodeBlend3_is_using_sync
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationNodeTimeScale = GodotAnimationNodeTimeScale GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeTimeScale where
        type BaseClass GodotAnimationNodeTimeScale = GodotAnimationNode
        super = coerce

newtype GodotAnimationNodeTimeSeek = GodotAnimationNodeTimeSeek GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeTimeSeek where
        type BaseClass GodotAnimationNodeTimeSeek = GodotAnimationNode
        super = coerce

newtype GodotAnimationNodeTransition = GodotAnimationNodeTransition GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotAnimationNodeTransition where
        type BaseClass GodotAnimationNodeTransition = GodotAnimationNode
        super = coerce
bindAnimationNodeTransition_set_enabled_inputs
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "set_enabled_inputs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_set_enabled_inputs #-}

instance Method "set_enabled_inputs" GodotAnimationNodeTransition
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_set_enabled_inputs
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeTransition_get_enabled_inputs
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "get_enabled_inputs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_get_enabled_inputs #-}

instance Method "get_enabled_inputs" GodotAnimationNodeTransition
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_get_enabled_inputs
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeTransition_set_input_as_auto_advance
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "set_input_as_auto_advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_set_input_as_auto_advance
             #-}

instance Method "set_input_as_auto_advance"
           GodotAnimationNodeTransition
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_set_input_as_auto_advance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeTransition_is_input_set_as_auto_advance
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "is_input_set_as_auto_advance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_is_input_set_as_auto_advance
             #-}

instance Method "is_input_set_as_auto_advance"
           GodotAnimationNodeTransition
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_is_input_set_as_auto_advance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeTransition_set_input_caption
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "set_input_caption" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_set_input_caption #-}

instance Method "set_input_caption" GodotAnimationNodeTransition
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_set_input_caption
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeTransition_get_input_caption
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "get_input_caption" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_get_input_caption #-}

instance Method "get_input_caption" GodotAnimationNodeTransition
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_get_input_caption
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeTransition_set_cross_fade_time
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "set_cross_fade_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_set_cross_fade_time #-}

instance Method "set_cross_fade_time" GodotAnimationNodeTransition
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_set_cross_fade_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimationNodeTransition_get_cross_fade_time
  = unsafePerformIO $
      withCString "AnimationNodeTransition" $
        \ clsNamePtr ->
          withCString "get_cross_fade_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimationNodeTransition_get_cross_fade_time #-}

instance Method "get_cross_fade_time" GodotAnimationNodeTransition
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimationNodeTransition_get_cross_fade_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCollisionObject = GodotCollisionObject GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotCollisionObject where
        type BaseClass GodotCollisionObject = GodotSpatial
        super = coerce
bindCollisionObject__input_event
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "_input_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject__input_event #-}

instance Method "_input_event" GodotCollisionObject
           (GodotObject ->
              GodotInputEvent -> GodotVector3 -> GodotVector3 -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject__input_event
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_set_ray_pickable
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "set_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_set_ray_pickable #-}

instance Method "set_ray_pickable" GodotCollisionObject
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_set_ray_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_is_ray_pickable
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "is_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_is_ray_pickable #-}

instance Method "is_ray_pickable" GodotCollisionObject (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_is_ray_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_set_capture_input_on_drag
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "set_capture_input_on_drag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_set_capture_input_on_drag #-}

instance Method "set_capture_input_on_drag" GodotCollisionObject
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject_set_capture_input_on_drag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_get_capture_input_on_drag
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "get_capture_input_on_drag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_get_capture_input_on_drag #-}

instance Method "get_capture_input_on_drag" GodotCollisionObject
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject_get_capture_input_on_drag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_get_rid
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "get_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_get_rid #-}

instance Method "get_rid" GodotCollisionObject (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_get_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_create_shape_owner
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "create_shape_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_create_shape_owner #-}

instance Method "create_shape_owner" GodotCollisionObject
           (GodotObject -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_create_shape_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_remove_shape_owner
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "remove_shape_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_remove_shape_owner #-}

instance Method "remove_shape_owner" GodotCollisionObject
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_remove_shape_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_get_shape_owners
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "get_shape_owners" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_get_shape_owners #-}

instance Method "get_shape_owners" GodotCollisionObject
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_get_shape_owners
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_set_transform
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_set_transform #-}

instance Method "shape_owner_set_transform" GodotCollisionObject
           (Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject_shape_owner_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_get_transform
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_get_transform #-}

instance Method "shape_owner_get_transform" GodotCollisionObject
           (Int -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject_shape_owner_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_get_owner
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_get_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_get_owner #-}

instance Method "shape_owner_get_owner" GodotCollisionObject
           (Int -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_shape_owner_get_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_set_disabled
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_set_disabled #-}

instance Method "shape_owner_set_disabled" GodotCollisionObject
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_shape_owner_set_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_is_shape_owner_disabled
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "is_shape_owner_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_is_shape_owner_disabled #-}

instance Method "is_shape_owner_disabled" GodotCollisionObject
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_is_shape_owner_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_add_shape
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_add_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_add_shape #-}

instance Method "shape_owner_add_shape" GodotCollisionObject
           (Int -> GodotShape -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_shape_owner_add_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_get_shape_count
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_get_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_get_shape_count #-}

instance Method "shape_owner_get_shape_count" GodotCollisionObject
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject_shape_owner_get_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_get_shape
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_get_shape #-}

instance Method "shape_owner_get_shape" GodotCollisionObject
           (Int -> Int -> IO GodotShape)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_shape_owner_get_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_get_shape_index
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_get_shape_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_get_shape_index #-}

instance Method "shape_owner_get_shape_index" GodotCollisionObject
           (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject_shape_owner_get_shape_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_remove_shape
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_remove_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_remove_shape #-}

instance Method "shape_owner_remove_shape" GodotCollisionObject
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_shape_owner_remove_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_owner_clear_shapes
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_owner_clear_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_owner_clear_shapes #-}

instance Method "shape_owner_clear_shapes" GodotCollisionObject
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_shape_owner_clear_shapes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject_shape_find_owner
  = unsafePerformIO $
      withCString "CollisionObject" $
        \ clsNamePtr ->
          withCString "shape_find_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject_shape_find_owner #-}

instance Method "shape_find_owner" GodotCollisionObject
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject_shape_find_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsBody = GodotPhysicsBody GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotPhysicsBody where
        type BaseClass GodotPhysicsBody = GodotCollisionObject
        super = coerce
bindPhysicsBody_set_collision_layer
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_set_collision_layer #-}

instance Method "set_collision_layer" GodotPhysicsBody
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_get_collision_layer
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_get_collision_layer #-}

instance Method "get_collision_layer" GodotPhysicsBody (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_get_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_set_collision_mask
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_set_collision_mask #-}

instance Method "set_collision_mask" GodotPhysicsBody
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_get_collision_mask
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_get_collision_mask #-}

instance Method "get_collision_mask" GodotPhysicsBody (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_set_collision_mask_bit
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotPhysicsBody
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_get_collision_mask_bit
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotPhysicsBody
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_set_collision_layer_bit
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "set_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_set_collision_layer_bit #-}

instance Method "set_collision_layer_bit" GodotPhysicsBody
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_set_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_get_collision_layer_bit
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "get_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_get_collision_layer_bit #-}

instance Method "get_collision_layer_bit" GodotPhysicsBody
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_get_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody__set_layers
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "_set_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody__set_layers #-}

instance Method "_set_layers" GodotPhysicsBody (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody__set_layers (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody__get_layers
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "_get_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody__get_layers #-}

instance Method "_get_layers" GodotPhysicsBody (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody__get_layers (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_get_collision_exceptions
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "get_collision_exceptions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_get_collision_exceptions #-}

instance Method "get_collision_exceptions" GodotPhysicsBody
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_get_collision_exceptions
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_add_collision_exception_with
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "add_collision_exception_with" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_add_collision_exception_with #-}

instance Method "add_collision_exception_with" GodotPhysicsBody
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody_add_collision_exception_with
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody_remove_collision_exception_with
  = unsafePerformIO $
      withCString "PhysicsBody" $
        \ clsNamePtr ->
          withCString "remove_collision_exception_with" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody_remove_collision_exception_with #-}

instance Method "remove_collision_exception_with" GodotPhysicsBody
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsBody_remove_collision_exception_with
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStaticBody = GodotStaticBody GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotStaticBody where
        type BaseClass GodotStaticBody = GodotPhysicsBody
        super = coerce
bindStaticBody_set_constant_linear_velocity
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "set_constant_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_set_constant_linear_velocity #-}

instance Method "set_constant_linear_velocity" GodotStaticBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_set_constant_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_set_constant_angular_velocity
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "set_constant_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_set_constant_angular_velocity #-}

instance Method "set_constant_angular_velocity" GodotStaticBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_set_constant_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_get_constant_linear_velocity
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "get_constant_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_get_constant_linear_velocity #-}

instance Method "get_constant_linear_velocity" GodotStaticBody
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_get_constant_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_get_constant_angular_velocity
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "get_constant_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_get_constant_angular_velocity #-}

instance Method "get_constant_angular_velocity" GodotStaticBody
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_get_constant_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_set_friction
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "set_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_set_friction #-}

instance Method "set_friction" GodotStaticBody (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_set_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_get_friction
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "get_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_get_friction #-}

instance Method "get_friction" GodotStaticBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_get_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_set_bounce
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "set_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_set_bounce #-}

instance Method "set_bounce" GodotStaticBody (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_set_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_get_bounce
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "get_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_get_bounce #-}

instance Method "get_bounce" GodotStaticBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_get_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_set_physics_material_override
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "set_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_set_physics_material_override #-}

instance Method "set_physics_material_override" GodotStaticBody
           (GodotPhysicsMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_set_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody_get_physics_material_override
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "get_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody_get_physics_material_override #-}

instance Method "get_physics_material_override" GodotStaticBody
           (IO GodotPhysicsMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody_get_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody__reload_physics_characteristics
  = unsafePerformIO $
      withCString "StaticBody" $
        \ clsNamePtr ->
          withCString "_reload_physics_characteristics" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody__reload_physics_characteristics #-}

instance Method "_reload_physics_characteristics" GodotStaticBody
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody__reload_physics_characteristics
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsMaterial = GodotPhysicsMaterial GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotPhysicsMaterial where
        type BaseClass GodotPhysicsMaterial = GodotResource
        super = coerce
bindPhysicsMaterial_set_friction
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "set_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_set_friction #-}

instance Method "set_friction" GodotPhysicsMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_set_friction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsMaterial_get_friction
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "get_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_get_friction #-}

instance Method "get_friction" GodotPhysicsMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_get_friction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsMaterial_set_rough
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "set_rough" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_set_rough #-}

instance Method "set_rough" GodotPhysicsMaterial (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_set_rough (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsMaterial_is_rough
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "is_rough" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_is_rough #-}

instance Method "is_rough" GodotPhysicsMaterial (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_is_rough (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsMaterial_set_bounce
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "set_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_set_bounce #-}

instance Method "set_bounce" GodotPhysicsMaterial (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_set_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsMaterial_get_bounce
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "get_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_get_bounce #-}

instance Method "get_bounce" GodotPhysicsMaterial (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_get_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsMaterial_set_absorbent
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "set_absorbent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_set_absorbent #-}

instance Method "set_absorbent" GodotPhysicsMaterial
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_set_absorbent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsMaterial_is_absorbent
  = unsafePerformIO $
      withCString "PhysicsMaterial" $
        \ clsNamePtr ->
          withCString "is_absorbent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsMaterial_is_absorbent #-}

instance Method "is_absorbent" GodotPhysicsMaterial (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsMaterial_is_absorbent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRigidBody = GodotRigidBody GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotRigidBody where
        type BaseClass GodotRigidBody = GodotPhysicsBody
        super = coerce
bindRigidBody__integrate_forces
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "_integrate_forces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody__integrate_forces #-}

instance Method "_integrate_forces" GodotRigidBody
           (GodotPhysicsDirectBodyState -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody__integrate_forces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_mode
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_mode #-}

instance Method "set_mode" GodotRigidBody (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_mode
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_mode #-}

instance Method "get_mode" GodotRigidBody (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_mass
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_mass #-}

instance Method "set_mass" GodotRigidBody (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_mass (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_mass
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_mass #-}

instance Method "get_mass" GodotRigidBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_mass (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_weight
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_weight" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_weight #-}

instance Method "set_weight" GodotRigidBody (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_weight (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_weight
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_weight" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_weight #-}

instance Method "get_weight" GodotRigidBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_weight (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_friction
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_friction #-}

instance Method "set_friction" GodotRigidBody (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_friction
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_friction #-}

instance Method "get_friction" GodotRigidBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_bounce
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_bounce #-}

instance Method "set_bounce" GodotRigidBody (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_bounce (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_bounce
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_bounce #-}

instance Method "get_bounce" GodotRigidBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_bounce (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_physics_material_override
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_physics_material_override #-}

instance Method "set_physics_material_override" GodotRigidBody
           (GodotPhysicsMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_physics_material_override
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_physics_material_override #-}

instance Method "get_physics_material_override" GodotRigidBody
           (IO GodotPhysicsMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody__reload_physics_characteristics
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "_reload_physics_characteristics" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody__reload_physics_characteristics #-}

instance Method "_reload_physics_characteristics" GodotRigidBody
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody__reload_physics_characteristics
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_linear_velocity
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_linear_velocity #-}

instance Method "set_linear_velocity" GodotRigidBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_linear_velocity
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_linear_velocity #-}

instance Method "get_linear_velocity" GodotRigidBody
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_angular_velocity
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_angular_velocity #-}

instance Method "set_angular_velocity" GodotRigidBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_angular_velocity
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_angular_velocity #-}

instance Method "get_angular_velocity" GodotRigidBody
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_gravity_scale
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_gravity_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_gravity_scale #-}

instance Method "set_gravity_scale" GodotRigidBody (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_gravity_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_gravity_scale
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_gravity_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_gravity_scale #-}

instance Method "get_gravity_scale" GodotRigidBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_gravity_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_linear_damp
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_linear_damp #-}

instance Method "set_linear_damp" GodotRigidBody (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_linear_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_linear_damp
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_linear_damp #-}

instance Method "get_linear_damp" GodotRigidBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_linear_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_angular_damp
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_angular_damp #-}

instance Method "set_angular_damp" GodotRigidBody (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_angular_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_angular_damp
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_angular_damp #-}

instance Method "get_angular_damp" GodotRigidBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_angular_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_max_contacts_reported
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_max_contacts_reported #-}

instance Method "set_max_contacts_reported" GodotRigidBody
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_max_contacts_reported
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_max_contacts_reported #-}

instance Method "get_max_contacts_reported" GodotRigidBody (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_use_custom_integrator
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_use_custom_integrator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_use_custom_integrator #-}

instance Method "set_use_custom_integrator" GodotRigidBody
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_use_custom_integrator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_is_using_custom_integrator
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "is_using_custom_integrator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_is_using_custom_integrator #-}

instance Method "is_using_custom_integrator" GodotRigidBody
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_is_using_custom_integrator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_contact_monitor
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_contact_monitor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_contact_monitor #-}

instance Method "set_contact_monitor" GodotRigidBody
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_contact_monitor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_is_contact_monitor_enabled
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "is_contact_monitor_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_is_contact_monitor_enabled #-}

instance Method "is_contact_monitor_enabled" GodotRigidBody
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_is_contact_monitor_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_use_continuous_collision_detection
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_use_continuous_collision_detection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_use_continuous_collision_detection
             #-}

instance Method "set_use_continuous_collision_detection"
           GodotRigidBody
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody_set_use_continuous_collision_detection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_is_using_continuous_collision_detection
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "is_using_continuous_collision_detection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_is_using_continuous_collision_detection
             #-}

instance Method "is_using_continuous_collision_detection"
           GodotRigidBody
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody_is_using_continuous_collision_detection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_axis_velocity
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_axis_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_axis_velocity #-}

instance Method "set_axis_velocity" GodotRigidBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_axis_velocity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_add_central_force
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "add_central_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_add_central_force #-}

instance Method "add_central_force" GodotRigidBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_add_central_force (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_add_force
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "add_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_add_force #-}

instance Method "add_force" GodotRigidBody
           (GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_add_force (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_add_torque
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "add_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_add_torque #-}

instance Method "add_torque" GodotRigidBody (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_add_torque (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_apply_central_impulse
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "apply_central_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_apply_central_impulse #-}

instance Method "apply_central_impulse" GodotRigidBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_apply_central_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_apply_impulse
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "apply_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_apply_impulse #-}

instance Method "apply_impulse" GodotRigidBody
           (GodotVector3 -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_apply_impulse (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_apply_torque_impulse
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "apply_torque_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_apply_torque_impulse #-}

instance Method "apply_torque_impulse" GodotRigidBody
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_apply_torque_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_sleeping
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_sleeping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_sleeping #-}

instance Method "set_sleeping" GodotRigidBody (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_sleeping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_is_sleeping
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "is_sleeping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_is_sleeping #-}

instance Method "is_sleeping" GodotRigidBody (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_is_sleeping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_can_sleep
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_can_sleep" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_can_sleep #-}

instance Method "set_can_sleep" GodotRigidBody (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_can_sleep (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_is_able_to_sleep
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "is_able_to_sleep" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_is_able_to_sleep #-}

instance Method "is_able_to_sleep" GodotRigidBody (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_is_able_to_sleep (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody__direct_state_changed
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "_direct_state_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody__direct_state_changed #-}

instance Method "_direct_state_changed" GodotRigidBody
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody__direct_state_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody__body_enter_tree
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "_body_enter_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody__body_enter_tree #-}

instance Method "_body_enter_tree" GodotRigidBody (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody__body_enter_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody__body_exit_tree
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "_body_exit_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody__body_exit_tree #-}

instance Method "_body_exit_tree" GodotRigidBody (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody__body_exit_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_set_axis_lock
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "set_axis_lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_set_axis_lock #-}

instance Method "set_axis_lock" GodotRigidBody
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_set_axis_lock (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_axis_lock
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_axis_lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_axis_lock #-}

instance Method "get_axis_lock" GodotRigidBody (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_axis_lock (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody_get_colliding_bodies
  = unsafePerformIO $
      withCString "RigidBody" $
        \ clsNamePtr ->
          withCString "get_colliding_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody_get_colliding_bodies #-}

instance Method "get_colliding_bodies" GodotRigidBody
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody_get_colliding_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotKinematicCollision = GodotKinematicCollision GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotKinematicCollision where
        type BaseClass GodotKinematicCollision = GodotReference
        super = coerce
bindKinematicCollision_get_position
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_position #-}

instance Method "get_position" GodotKinematicCollision
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_normal
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_normal #-}

instance Method "get_normal" GodotKinematicCollision
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_travel
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_travel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_travel #-}

instance Method "get_travel" GodotKinematicCollision
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_travel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_remainder
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_remainder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_remainder #-}

instance Method "get_remainder" GodotKinematicCollision
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_remainder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_local_shape
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_local_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_local_shape #-}

instance Method "get_local_shape" GodotKinematicCollision
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_local_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_collider
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_collider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_collider #-}

instance Method "get_collider" GodotKinematicCollision
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_collider
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_collider_id
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_collider_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_collider_id #-}

instance Method "get_collider_id" GodotKinematicCollision (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_collider_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_collider_shape
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_collider_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_collider_shape #-}

instance Method "get_collider_shape" GodotKinematicCollision
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_collider_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_collider_shape_index
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_collider_shape_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_collider_shape_index #-}

instance Method "get_collider_shape_index" GodotKinematicCollision
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindKinematicCollision_get_collider_shape_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_collider_velocity
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_collider_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_collider_velocity #-}

instance Method "get_collider_velocity" GodotKinematicCollision
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_collider_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision_get_collider_metadata
  = unsafePerformIO $
      withCString "KinematicCollision" $
        \ clsNamePtr ->
          withCString "get_collider_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision_get_collider_metadata #-}

instance Method "get_collider_metadata" GodotKinematicCollision
           (IO GodotVariant)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision_get_collider_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotKinematicBody = GodotKinematicBody GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotKinematicBody where
        type BaseClass GodotKinematicBody = GodotPhysicsBody
        super = coerce
bindKinematicBody_move_and_collide
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "move_and_collide" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_move_and_collide #-}

instance Method "move_and_collide" GodotKinematicBody
           (GodotVector3 -> Bool -> Bool -> IO GodotKinematicCollision)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_move_and_collide
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_move_and_slide
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "move_and_slide" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_move_and_slide #-}

instance Method "move_and_slide" GodotKinematicBody
           (GodotVector3 ->
              GodotVector3 -> Bool -> Int -> Float -> Bool -> IO GodotVector3)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_move_and_slide
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_move_and_slide_with_snap
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "move_and_slide_with_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_move_and_slide_with_snap #-}

instance Method "move_and_slide_with_snap" GodotKinematicBody
           (GodotVector3 ->
              GodotVector3 ->
                GodotVector3 -> Bool -> Bool -> Int -> Float -> IO GodotVector3)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_move_and_slide_with_snap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_test_move
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "test_move" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_test_move #-}

instance Method "test_move" GodotKinematicBody
           (GodotTransform -> GodotVector3 -> Bool -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_test_move (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_is_on_floor
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "is_on_floor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_is_on_floor #-}

instance Method "is_on_floor" GodotKinematicBody (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_is_on_floor (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_is_on_ceiling
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "is_on_ceiling" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_is_on_ceiling #-}

instance Method "is_on_ceiling" GodotKinematicBody (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_is_on_ceiling (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_is_on_wall
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "is_on_wall" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_is_on_wall #-}

instance Method "is_on_wall" GodotKinematicBody (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_is_on_wall (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_get_floor_velocity
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "get_floor_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_get_floor_velocity #-}

instance Method "get_floor_velocity" GodotKinematicBody
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_get_floor_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_set_axis_lock
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "set_axis_lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_set_axis_lock #-}

instance Method "set_axis_lock" GodotKinematicBody
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_set_axis_lock (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_get_axis_lock
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "get_axis_lock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_get_axis_lock #-}

instance Method "get_axis_lock" GodotKinematicBody (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_get_axis_lock (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_set_safe_margin
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "set_safe_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_set_safe_margin #-}

instance Method "set_safe_margin" GodotKinematicBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_set_safe_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_get_safe_margin
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "get_safe_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_get_safe_margin #-}

instance Method "get_safe_margin" GodotKinematicBody (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_get_safe_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_get_slide_count
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "get_slide_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_get_slide_count #-}

instance Method "get_slide_count" GodotKinematicBody (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_get_slide_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody_get_slide_collision
  = unsafePerformIO $
      withCString "KinematicBody" $
        \ clsNamePtr ->
          withCString "get_slide_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody_get_slide_collision #-}

instance Method "get_slide_collision" GodotKinematicBody
           (Int -> IO GodotKinematicCollision)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody_get_slide_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpringArm = GodotSpringArm GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotSpringArm where
        type BaseClass GodotSpringArm = GodotSpatial
        super = coerce
bindSpringArm_get_hit_length
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "get_hit_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_get_hit_length #-}

instance Method "get_hit_length" GodotSpringArm (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_get_hit_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_set_length
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "set_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_set_length #-}

instance Method "set_length" GodotSpringArm (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_set_length (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_get_length
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "get_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_get_length #-}

instance Method "get_length" GodotSpringArm (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_get_length (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_set_shape
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_set_shape #-}

instance Method "set_shape" GodotSpringArm (GodotShape -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_set_shape (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_get_shape
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_get_shape #-}

instance Method "get_shape" GodotSpringArm (IO GodotShape) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_get_shape (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_add_excluded_object
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "add_excluded_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_add_excluded_object #-}

instance Method "add_excluded_object" GodotSpringArm
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_add_excluded_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_remove_excluded_object
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "remove_excluded_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_remove_excluded_object #-}

instance Method "remove_excluded_object" GodotSpringArm
           (GodotRid -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_remove_excluded_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_clear_excluded_objects
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "clear_excluded_objects" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_clear_excluded_objects #-}

instance Method "clear_excluded_objects" GodotSpringArm (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_clear_excluded_objects
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_set_collision_mask
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_set_collision_mask #-}

instance Method "set_collision_mask" GodotSpringArm (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_get_collision_mask
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_get_collision_mask #-}

instance Method "get_collision_mask" GodotSpringArm (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_set_margin
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "set_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_set_margin #-}

instance Method "set_margin" GodotSpringArm (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_set_margin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpringArm_get_margin
  = unsafePerformIO $
      withCString "SpringArm" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpringArm_get_margin #-}

instance Method "get_margin" GodotSpringArm (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpringArm_get_margin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotShape = GodotShape GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotShape where
        type BaseClass GodotShape = GodotResource
        super = coerce
bindShape_set_margin
  = unsafePerformIO $
      withCString "Shape" $
        \ clsNamePtr ->
          withCString "set_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape_set_margin #-}

instance Method "set_margin" GodotShape (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShape_set_margin (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShape_get_margin
  = unsafePerformIO $
      withCString "Shape" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape_get_margin #-}

instance Method "get_margin" GodotShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShape_get_margin (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicalBone = GodotPhysicalBone GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotPhysicalBone where
        type BaseClass GodotPhysicalBone = GodotPhysicsBody
        super = coerce
bindPhysicalBone__direct_state_changed
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "_direct_state_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone__direct_state_changed #-}

instance Method "_direct_state_changed" GodotPhysicalBone
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone__direct_state_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_joint_type
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_joint_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_joint_type #-}

instance Method "set_joint_type" GodotPhysicalBone (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_joint_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_joint_type
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_joint_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_joint_type #-}

instance Method "get_joint_type" GodotPhysicalBone (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_joint_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_joint_offset
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_joint_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_joint_offset #-}

instance Method "set_joint_offset" GodotPhysicalBone
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_joint_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_joint_offset
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_joint_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_joint_offset #-}

instance Method "get_joint_offset" GodotPhysicalBone
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_joint_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_body_offset
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_body_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_body_offset #-}

instance Method "set_body_offset" GodotPhysicalBone
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_body_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_body_offset
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_body_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_body_offset #-}

instance Method "get_body_offset" GodotPhysicalBone
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_body_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_is_static_body
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "is_static_body" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_is_static_body #-}

instance Method "is_static_body" GodotPhysicalBone (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_is_static_body (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_simulate_physics
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_simulate_physics" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_simulate_physics #-}

instance Method "get_simulate_physics" GodotPhysicalBone (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_simulate_physics
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_is_simulating_physics
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "is_simulating_physics" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_is_simulating_physics #-}

instance Method "is_simulating_physics" GodotPhysicalBone (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_is_simulating_physics
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_bone_id
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_bone_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_bone_id #-}

instance Method "get_bone_id" GodotPhysicalBone (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_bone_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_mass
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_mass #-}

instance Method "set_mass" GodotPhysicalBone (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_mass (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_mass
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_mass #-}

instance Method "get_mass" GodotPhysicalBone (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_mass (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_weight
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_weight" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_weight #-}

instance Method "set_weight" GodotPhysicalBone (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_weight (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_weight
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_weight" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_weight #-}

instance Method "get_weight" GodotPhysicalBone (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_weight (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_friction
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_friction #-}

instance Method "set_friction" GodotPhysicalBone (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_friction
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_friction #-}

instance Method "get_friction" GodotPhysicalBone (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_bounce
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_bounce #-}

instance Method "set_bounce" GodotPhysicalBone (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_bounce
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_bounce #-}

instance Method "get_bounce" GodotPhysicalBone (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_set_gravity_scale
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "set_gravity_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_set_gravity_scale #-}

instance Method "set_gravity_scale" GodotPhysicalBone
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_set_gravity_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicalBone_get_gravity_scale
  = unsafePerformIO $
      withCString "PhysicalBone" $
        \ clsNamePtr ->
          withCString "get_gravity_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicalBone_get_gravity_scale #-}

instance Method "get_gravity_scale" GodotPhysicalBone (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicalBone_get_gravity_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSoftBody = GodotSoftBody GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotSoftBody where
        type BaseClass GodotSoftBody = GodotMeshInstance
        super = coerce
bindSoftBody__draw_soft_mesh
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "_draw_soft_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody__draw_soft_mesh #-}

instance Method "_draw_soft_mesh" GodotSoftBody (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody__draw_soft_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_collision_mask
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_collision_mask #-}

instance Method "set_collision_mask" GodotSoftBody (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_collision_mask
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_collision_mask #-}

instance Method "get_collision_mask" GodotSoftBody (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_collision_layer
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_collision_layer #-}

instance Method "set_collision_layer" GodotSoftBody (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_collision_layer
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_collision_layer #-}

instance Method "get_collision_layer" GodotSoftBody (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_collision_mask_bit
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotSoftBody
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_collision_mask_bit
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotSoftBody
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_collision_layer_bit
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_collision_layer_bit #-}

instance Method "set_collision_layer_bit" GodotSoftBody
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_collision_layer_bit
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_collision_layer_bit #-}

instance Method "get_collision_layer_bit" GodotSoftBody
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_parent_collision_ignore
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_parent_collision_ignore" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_parent_collision_ignore #-}

instance Method "set_parent_collision_ignore" GodotSoftBody
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_parent_collision_ignore
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_parent_collision_ignore
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_parent_collision_ignore" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_parent_collision_ignore #-}

instance Method "get_parent_collision_ignore" GodotSoftBody
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_parent_collision_ignore
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_collision_exceptions
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_collision_exceptions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_collision_exceptions #-}

instance Method "get_collision_exceptions" GodotSoftBody
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_collision_exceptions
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_add_collision_exception_with
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "add_collision_exception_with" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_add_collision_exception_with #-}

instance Method "add_collision_exception_with" GodotSoftBody
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_add_collision_exception_with
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_remove_collision_exception_with
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "remove_collision_exception_with" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_remove_collision_exception_with #-}

instance Method "remove_collision_exception_with" GodotSoftBody
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_remove_collision_exception_with
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_simulation_precision
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_simulation_precision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_simulation_precision #-}

instance Method "set_simulation_precision" GodotSoftBody
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_simulation_precision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_simulation_precision
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_simulation_precision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_simulation_precision #-}

instance Method "get_simulation_precision" GodotSoftBody (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_simulation_precision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_total_mass
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_total_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_total_mass #-}

instance Method "set_total_mass" GodotSoftBody (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_total_mass (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_total_mass
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_total_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_total_mass #-}

instance Method "get_total_mass" GodotSoftBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_total_mass (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_linear_stiffness
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_linear_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_linear_stiffness #-}

instance Method "set_linear_stiffness" GodotSoftBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_linear_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_linear_stiffness
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_linear_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_linear_stiffness #-}

instance Method "get_linear_stiffness" GodotSoftBody (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_linear_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_areaAngular_stiffness
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_areaAngular_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_areaAngular_stiffness #-}

instance Method "set_areaAngular_stiffness" GodotSoftBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_areaAngular_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_areaAngular_stiffness
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_areaAngular_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_areaAngular_stiffness #-}

instance Method "get_areaAngular_stiffness" GodotSoftBody
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_areaAngular_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_volume_stiffness
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_volume_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_volume_stiffness #-}

instance Method "set_volume_stiffness" GodotSoftBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_volume_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_volume_stiffness
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_volume_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_volume_stiffness #-}

instance Method "get_volume_stiffness" GodotSoftBody (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_volume_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_pressure_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_pressure_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_pressure_coefficient #-}

instance Method "set_pressure_coefficient" GodotSoftBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_pressure_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_pressure_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_pressure_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_pressure_coefficient #-}

instance Method "get_pressure_coefficient" GodotSoftBody (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_pressure_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_pose_matching_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_pose_matching_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_pose_matching_coefficient #-}

instance Method "set_pose_matching_coefficient" GodotSoftBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_pose_matching_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_pose_matching_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_pose_matching_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_pose_matching_coefficient #-}

instance Method "get_pose_matching_coefficient" GodotSoftBody
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_pose_matching_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_damping_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_damping_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_damping_coefficient #-}

instance Method "set_damping_coefficient" GodotSoftBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_damping_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_damping_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_damping_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_damping_coefficient #-}

instance Method "get_damping_coefficient" GodotSoftBody (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_damping_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_drag_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_drag_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_drag_coefficient #-}

instance Method "set_drag_coefficient" GodotSoftBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_drag_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_get_drag_coefficient
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "get_drag_coefficient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_get_drag_coefficient #-}

instance Method "get_drag_coefficient" GodotSoftBody (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_get_drag_coefficient
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_set_ray_pickable
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "set_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_set_ray_pickable #-}

instance Method "set_ray_pickable" GodotSoftBody (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_set_ray_pickable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSoftBody_is_ray_pickable
  = unsafePerformIO $
      withCString "SoftBody" $
        \ clsNamePtr ->
          withCString "is_ray_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSoftBody_is_ray_pickable #-}

instance Method "is_ray_pickable" GodotSoftBody (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSoftBody_is_ray_pickable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSkeletonIK = GodotSkeletonIK GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotSkeletonIK where
        type BaseClass GodotSkeletonIK = GodotNode
        super = coerce
bindSkeletonIK_set_root_bone
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_root_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_root_bone #-}

instance Method "set_root_bone" GodotSkeletonIK
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_root_bone (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_root_bone
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_root_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_root_bone #-}

instance Method "get_root_bone" GodotSkeletonIK (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_root_bone (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_tip_bone
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_tip_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_tip_bone #-}

instance Method "set_tip_bone" GodotSkeletonIK
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_tip_bone (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_tip_bone
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_tip_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_tip_bone #-}

instance Method "get_tip_bone" GodotSkeletonIK (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_tip_bone (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_interpolation
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_interpolation #-}

instance Method "set_interpolation" GodotSkeletonIK
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_interpolation
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_interpolation #-}

instance Method "get_interpolation" GodotSkeletonIK (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_target_transform
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_target_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_target_transform #-}

instance Method "set_target_transform" GodotSkeletonIK
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_target_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_target_transform
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_target_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_target_transform #-}

instance Method "get_target_transform" GodotSkeletonIK
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_target_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_target_node
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_target_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_target_node #-}

instance Method "set_target_node" GodotSkeletonIK
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_target_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_target_node
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_target_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_target_node #-}

instance Method "get_target_node" GodotSkeletonIK
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_target_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_use_magnet
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_use_magnet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_use_magnet #-}

instance Method "set_use_magnet" GodotSkeletonIK (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_use_magnet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_is_using_magnet
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "is_using_magnet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_is_using_magnet #-}

instance Method "is_using_magnet" GodotSkeletonIK (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_is_using_magnet (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_magnet_position
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_magnet_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_magnet_position #-}

instance Method "set_magnet_position" GodotSkeletonIK
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_magnet_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_magnet_position
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_magnet_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_magnet_position #-}

instance Method "get_magnet_position" GodotSkeletonIK
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_magnet_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_parent_skeleton
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_parent_skeleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_parent_skeleton #-}

instance Method "get_parent_skeleton" GodotSkeletonIK
           (IO GodotSkeleton)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_parent_skeleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_is_running
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "is_running" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_is_running #-}

instance Method "is_running" GodotSkeletonIK (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_is_running (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_min_distance
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_min_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_min_distance #-}

instance Method "set_min_distance" GodotSkeletonIK (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_min_distance (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_min_distance
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_min_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_min_distance #-}

instance Method "get_min_distance" GodotSkeletonIK (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_min_distance (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_set_max_iterations
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "set_max_iterations" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_set_max_iterations #-}

instance Method "set_max_iterations" GodotSkeletonIK (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_set_max_iterations
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_get_max_iterations
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "get_max_iterations" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_get_max_iterations #-}

instance Method "get_max_iterations" GodotSkeletonIK (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_get_max_iterations
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_start
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_start #-}

instance Method "start" GodotSkeletonIK (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_start (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeletonIK_stop
  = unsafePerformIO $
      withCString "SkeletonIK" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeletonIK_stop #-}

instance Method "stop" GodotSkeletonIK (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeletonIK_stop (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBoneAttachment = GodotBoneAttachment GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotBoneAttachment where
        type BaseClass GodotBoneAttachment = GodotSpatial
        super = coerce
bindBoneAttachment_set_bone_name
  = unsafePerformIO $
      withCString "BoneAttachment" $
        \ clsNamePtr ->
          withCString "set_bone_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBoneAttachment_set_bone_name #-}

instance Method "set_bone_name" GodotBoneAttachment
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBoneAttachment_set_bone_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBoneAttachment_get_bone_name
  = unsafePerformIO $
      withCString "BoneAttachment" $
        \ clsNamePtr ->
          withCString "get_bone_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBoneAttachment_get_bone_name #-}

instance Method "get_bone_name" GodotBoneAttachment
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBoneAttachment_get_bone_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVehicleBody = GodotVehicleBody GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotVehicleBody where
        type BaseClass GodotVehicleBody = GodotRigidBody
        super = coerce
bindVehicleBody_set_engine_force
  = unsafePerformIO $
      withCString "VehicleBody" $
        \ clsNamePtr ->
          withCString "set_engine_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleBody_set_engine_force #-}

instance Method "set_engine_force" GodotVehicleBody
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleBody_set_engine_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleBody_get_engine_force
  = unsafePerformIO $
      withCString "VehicleBody" $
        \ clsNamePtr ->
          withCString "get_engine_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleBody_get_engine_force #-}

instance Method "get_engine_force" GodotVehicleBody (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleBody_get_engine_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleBody_set_brake
  = unsafePerformIO $
      withCString "VehicleBody" $
        \ clsNamePtr ->
          withCString "set_brake" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleBody_set_brake #-}

instance Method "set_brake" GodotVehicleBody (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleBody_set_brake (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleBody_get_brake
  = unsafePerformIO $
      withCString "VehicleBody" $
        \ clsNamePtr ->
          withCString "get_brake" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleBody_get_brake #-}

instance Method "get_brake" GodotVehicleBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleBody_get_brake (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleBody_set_steering
  = unsafePerformIO $
      withCString "VehicleBody" $
        \ clsNamePtr ->
          withCString "set_steering" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleBody_set_steering #-}

instance Method "set_steering" GodotVehicleBody (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleBody_set_steering (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleBody_get_steering
  = unsafePerformIO $
      withCString "VehicleBody" $
        \ clsNamePtr ->
          withCString "get_steering" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleBody_get_steering #-}

instance Method "get_steering" GodotVehicleBody (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleBody_get_steering (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVehicleWheel = GodotVehicleWheel GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotVehicleWheel where
        type BaseClass GodotVehicleWheel = GodotSpatial
        super = coerce
bindVehicleWheel_set_radius
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_radius #-}

instance Method "set_radius" GodotVehicleWheel (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_radius
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_radius #-}

instance Method "get_radius" GodotVehicleWheel (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_suspension_rest_length
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_suspension_rest_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_suspension_rest_length #-}

instance Method "set_suspension_rest_length" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_suspension_rest_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_suspension_rest_length
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_suspension_rest_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_suspension_rest_length #-}

instance Method "get_suspension_rest_length" GodotVehicleWheel
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_suspension_rest_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_suspension_travel
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_suspension_travel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_suspension_travel #-}

instance Method "set_suspension_travel" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_suspension_travel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_suspension_travel
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_suspension_travel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_suspension_travel #-}

instance Method "get_suspension_travel" GodotVehicleWheel
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_suspension_travel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_suspension_stiffness
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_suspension_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_suspension_stiffness #-}

instance Method "set_suspension_stiffness" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_suspension_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_suspension_stiffness
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_suspension_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_suspension_stiffness #-}

instance Method "get_suspension_stiffness" GodotVehicleWheel
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_suspension_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_suspension_max_force
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_suspension_max_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_suspension_max_force #-}

instance Method "set_suspension_max_force" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_suspension_max_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_suspension_max_force
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_suspension_max_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_suspension_max_force #-}

instance Method "get_suspension_max_force" GodotVehicleWheel
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_suspension_max_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_damping_compression
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_damping_compression" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_damping_compression #-}

instance Method "set_damping_compression" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_damping_compression
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_damping_compression
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_damping_compression" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_damping_compression #-}

instance Method "get_damping_compression" GodotVehicleWheel
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_damping_compression
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_damping_relaxation
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_damping_relaxation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_damping_relaxation #-}

instance Method "set_damping_relaxation" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_damping_relaxation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_damping_relaxation
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_damping_relaxation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_damping_relaxation #-}

instance Method "get_damping_relaxation" GodotVehicleWheel
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_damping_relaxation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_use_as_traction
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_use_as_traction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_use_as_traction #-}

instance Method "set_use_as_traction" GodotVehicleWheel
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_use_as_traction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_is_used_as_traction
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "is_used_as_traction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_is_used_as_traction #-}

instance Method "is_used_as_traction" GodotVehicleWheel (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_is_used_as_traction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_use_as_steering
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_use_as_steering" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_use_as_steering #-}

instance Method "set_use_as_steering" GodotVehicleWheel
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_use_as_steering
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_is_used_as_steering
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "is_used_as_steering" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_is_used_as_steering #-}

instance Method "is_used_as_steering" GodotVehicleWheel (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_is_used_as_steering
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_friction_slip
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_friction_slip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_friction_slip #-}

instance Method "set_friction_slip" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_friction_slip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_friction_slip
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_friction_slip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_friction_slip #-}

instance Method "get_friction_slip" GodotVehicleWheel (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_friction_slip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_is_in_contact
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "is_in_contact" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_is_in_contact #-}

instance Method "is_in_contact" GodotVehicleWheel (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_is_in_contact (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_set_roll_influence
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "set_roll_influence" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_set_roll_influence #-}

instance Method "set_roll_influence" GodotVehicleWheel
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_set_roll_influence
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_roll_influence
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_roll_influence" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_roll_influence #-}

instance Method "get_roll_influence" GodotVehicleWheel (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_roll_influence
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVehicleWheel_get_skidinfo
  = unsafePerformIO $
      withCString "VehicleWheel" $
        \ clsNamePtr ->
          withCString "get_skidinfo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVehicleWheel_get_skidinfo #-}

instance Method "get_skidinfo" GodotVehicleWheel (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVehicleWheel_get_skidinfo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotArea = GodotArea GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotArea where
        type BaseClass GodotArea = GodotCollisionObject
        super = coerce
bindArea__body_enter_tree
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "_body_enter_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea__body_enter_tree #-}

instance Method "_body_enter_tree" GodotArea (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea__body_enter_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea__body_exit_tree
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "_body_exit_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea__body_exit_tree #-}

instance Method "_body_exit_tree" GodotArea (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea__body_exit_tree (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea__area_enter_tree
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "_area_enter_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea__area_enter_tree #-}

instance Method "_area_enter_tree" GodotArea (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea__area_enter_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea__area_exit_tree
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "_area_exit_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea__area_exit_tree #-}

instance Method "_area_exit_tree" GodotArea (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea__area_exit_tree (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_space_override_mode
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_space_override_mode #-}

instance Method "set_space_override_mode" GodotArea (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_space_override_mode
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_space_override_mode #-}

instance Method "get_space_override_mode" GodotArea (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_gravity_is_point
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_gravity_is_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_gravity_is_point #-}

instance Method "set_gravity_is_point" GodotArea (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_gravity_is_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_is_gravity_a_point
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "is_gravity_a_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_is_gravity_a_point #-}

instance Method "is_gravity_a_point" GodotArea (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_is_gravity_a_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_gravity_distance_scale
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_gravity_distance_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_gravity_distance_scale #-}

instance Method "set_gravity_distance_scale" GodotArea
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_gravity_distance_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_gravity_distance_scale
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_gravity_distance_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_gravity_distance_scale #-}

instance Method "get_gravity_distance_scale" GodotArea (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_gravity_distance_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_gravity_vector
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_gravity_vector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_gravity_vector #-}

instance Method "set_gravity_vector" GodotArea
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_gravity_vector (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_gravity_vector
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_gravity_vector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_gravity_vector #-}

instance Method "get_gravity_vector" GodotArea (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_gravity_vector (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_gravity
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_gravity #-}

instance Method "set_gravity" GodotArea (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_gravity (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_gravity
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_gravity #-}

instance Method "get_gravity" GodotArea (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_gravity (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_angular_damp
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_angular_damp #-}

instance Method "set_angular_damp" GodotArea (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_angular_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_angular_damp
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_angular_damp #-}

instance Method "get_angular_damp" GodotArea (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_angular_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_linear_damp
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_linear_damp #-}

instance Method "set_linear_damp" GodotArea (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_linear_damp (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_linear_damp
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_linear_damp #-}

instance Method "get_linear_damp" GodotArea (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_linear_damp (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_priority
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_priority #-}

instance Method "set_priority" GodotArea (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_priority (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_priority
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_priority #-}

instance Method "get_priority" GodotArea (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_priority (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_collision_mask
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_collision_mask #-}

instance Method "set_collision_mask" GodotArea (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_collision_mask
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_collision_mask #-}

instance Method "get_collision_mask" GodotArea (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_collision_layer
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_collision_layer #-}

instance Method "set_collision_layer" GodotArea (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_collision_layer
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_collision_layer #-}

instance Method "get_collision_layer" GodotArea (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_collision_mask_bit
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotArea
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_collision_mask_bit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_collision_mask_bit
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotArea (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_collision_mask_bit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_collision_layer_bit
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_collision_layer_bit #-}

instance Method "set_collision_layer_bit" GodotArea
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_collision_layer_bit
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_collision_layer_bit #-}

instance Method "get_collision_layer_bit" GodotArea
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_monitorable
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_monitorable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_monitorable #-}

instance Method "set_monitorable" GodotArea (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_monitorable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_is_monitorable
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "is_monitorable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_is_monitorable #-}

instance Method "is_monitorable" GodotArea (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_is_monitorable (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_monitoring
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_monitoring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_monitoring #-}

instance Method "set_monitoring" GodotArea (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_monitoring (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_is_monitoring
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "is_monitoring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_is_monitoring #-}

instance Method "is_monitoring" GodotArea (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_is_monitoring (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_overlapping_bodies
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_overlapping_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_overlapping_bodies #-}

instance Method "get_overlapping_bodies" GodotArea (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_overlapping_bodies (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_overlapping_areas
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_overlapping_areas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_overlapping_areas #-}

instance Method "get_overlapping_areas" GodotArea (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_overlapping_areas (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_overlaps_body
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "overlaps_body" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_overlaps_body #-}

instance Method "overlaps_body" GodotArea (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_overlaps_body (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_overlaps_area
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "overlaps_area" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_overlaps_area #-}

instance Method "overlaps_area" GodotArea (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_overlaps_area (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea__body_inout
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "_body_inout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea__body_inout #-}

instance Method "_body_inout" GodotArea
           (Int -> GodotRid -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea__body_inout (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea__area_inout
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "_area_inout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea__area_inout #-}

instance Method "_area_inout" GodotArea
           (Int -> GodotRid -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea__area_inout (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_audio_bus_override
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_audio_bus_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_audio_bus_override #-}

instance Method "set_audio_bus_override" GodotArea (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_audio_bus_override (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_is_overriding_audio_bus
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "is_overriding_audio_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_is_overriding_audio_bus #-}

instance Method "is_overriding_audio_bus" GodotArea (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_is_overriding_audio_bus
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_audio_bus
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_audio_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_audio_bus #-}

instance Method "set_audio_bus" GodotArea (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_audio_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_audio_bus
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_audio_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_audio_bus #-}

instance Method "get_audio_bus" GodotArea (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_audio_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_use_reverb_bus
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_use_reverb_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_use_reverb_bus #-}

instance Method "set_use_reverb_bus" GodotArea (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_use_reverb_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_is_using_reverb_bus
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "is_using_reverb_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_is_using_reverb_bus #-}

instance Method "is_using_reverb_bus" GodotArea (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_is_using_reverb_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_reverb_bus
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_reverb_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_reverb_bus #-}

instance Method "set_reverb_bus" GodotArea (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_reverb_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_reverb_bus
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_reverb_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_reverb_bus #-}

instance Method "get_reverb_bus" GodotArea (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_reverb_bus (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_reverb_amount
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_reverb_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_reverb_amount #-}

instance Method "set_reverb_amount" GodotArea (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_reverb_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_reverb_amount
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_reverb_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_reverb_amount #-}

instance Method "get_reverb_amount" GodotArea (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_reverb_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_set_reverb_uniformity
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "set_reverb_uniformity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_set_reverb_uniformity #-}

instance Method "set_reverb_uniformity" GodotArea (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_set_reverb_uniformity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea_get_reverb_uniformity
  = unsafePerformIO $
      withCString "Area" $
        \ clsNamePtr ->
          withCString "get_reverb_uniformity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea_get_reverb_uniformity #-}

instance Method "get_reverb_uniformity" GodotArea (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea_get_reverb_uniformity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotProximityGroup = GodotProximityGroup GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotProximityGroup where
        type BaseClass GodotProximityGroup = GodotSpatial
        super = coerce
bindProximityGroup_set_group_name
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "set_group_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup_set_group_name #-}

instance Method "set_group_name" GodotProximityGroup
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProximityGroup_set_group_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProximityGroup_get_group_name
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "get_group_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup_get_group_name #-}

instance Method "get_group_name" GodotProximityGroup
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProximityGroup_get_group_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProximityGroup_set_dispatch_mode
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "set_dispatch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup_set_dispatch_mode #-}

instance Method "set_dispatch_mode" GodotProximityGroup
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProximityGroup_set_dispatch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProximityGroup_get_dispatch_mode
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "get_dispatch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup_get_dispatch_mode #-}

instance Method "get_dispatch_mode" GodotProximityGroup (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProximityGroup_get_dispatch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProximityGroup_set_grid_radius
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "set_grid_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup_set_grid_radius #-}

instance Method "set_grid_radius" GodotProximityGroup
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProximityGroup_set_grid_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProximityGroup_get_grid_radius
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "get_grid_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup_get_grid_radius #-}

instance Method "get_grid_radius" GodotProximityGroup
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProximityGroup_get_grid_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProximityGroup_broadcast
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "broadcast" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup_broadcast #-}

instance Method "broadcast" GodotProximityGroup
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProximityGroup_broadcast (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProximityGroup__proximity_group_broadcast
  = unsafePerformIO $
      withCString "ProximityGroup" $
        \ clsNamePtr ->
          withCString "_proximity_group_broadcast" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProximityGroup__proximity_group_broadcast #-}

instance Method "_proximity_group_broadcast" GodotProximityGroup
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindProximityGroup__proximity_group_broadcast
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCollisionShape = GodotCollisionShape GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotCollisionShape where
        type BaseClass GodotCollisionShape = GodotSpatial
        super = coerce
bindCollisionShape_resource_changed
  = unsafePerformIO $
      withCString "CollisionShape" $
        \ clsNamePtr ->
          withCString "resource_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape_resource_changed #-}

instance Method "resource_changed" GodotCollisionShape
           (GodotResource -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape_resource_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape_set_shape
  = unsafePerformIO $
      withCString "CollisionShape" $
        \ clsNamePtr ->
          withCString "set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape_set_shape #-}

instance Method "set_shape" GodotCollisionShape
           (GodotShape -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape_set_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape_get_shape
  = unsafePerformIO $
      withCString "CollisionShape" $
        \ clsNamePtr ->
          withCString "get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape_get_shape #-}

instance Method "get_shape" GodotCollisionShape (IO GodotShape)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape_get_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape_set_disabled
  = unsafePerformIO $
      withCString "CollisionShape" $
        \ clsNamePtr ->
          withCString "set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape_set_disabled #-}

instance Method "set_disabled" GodotCollisionShape (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape_set_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape_is_disabled
  = unsafePerformIO $
      withCString "CollisionShape" $
        \ clsNamePtr ->
          withCString "is_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape_is_disabled #-}

instance Method "is_disabled" GodotCollisionShape (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape_is_disabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape_make_convex_from_brothers
  = unsafePerformIO $
      withCString "CollisionShape" $
        \ clsNamePtr ->
          withCString "make_convex_from_brothers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape_make_convex_from_brothers #-}

instance Method "make_convex_from_brothers" GodotCollisionShape
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape_make_convex_from_brothers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCollisionPolygon = GodotCollisionPolygon GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotCollisionPolygon where
        type BaseClass GodotCollisionPolygon = GodotSpatial
        super = coerce
bindCollisionPolygon_set_depth
  = unsafePerformIO $
      withCString "CollisionPolygon" $
        \ clsNamePtr ->
          withCString "set_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon_set_depth #-}

instance Method "set_depth" GodotCollisionPolygon (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon_set_depth (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon_get_depth
  = unsafePerformIO $
      withCString "CollisionPolygon" $
        \ clsNamePtr ->
          withCString "get_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon_get_depth #-}

instance Method "get_depth" GodotCollisionPolygon (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon_get_depth (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon_set_polygon
  = unsafePerformIO $
      withCString "CollisionPolygon" $
        \ clsNamePtr ->
          withCString "set_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon_set_polygon #-}

instance Method "set_polygon" GodotCollisionPolygon
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon_set_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon_get_polygon
  = unsafePerformIO $
      withCString "CollisionPolygon" $
        \ clsNamePtr ->
          withCString "get_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon_get_polygon #-}

instance Method "get_polygon" GodotCollisionPolygon
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon_get_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon_set_disabled
  = unsafePerformIO $
      withCString "CollisionPolygon" $
        \ clsNamePtr ->
          withCString "set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon_set_disabled #-}

instance Method "set_disabled" GodotCollisionPolygon
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon_set_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon_is_disabled
  = unsafePerformIO $
      withCString "CollisionPolygon" $
        \ clsNamePtr ->
          withCString "is_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon_is_disabled #-}

instance Method "is_disabled" GodotCollisionPolygon (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon_is_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon__is_editable_3d_polygon
  = unsafePerformIO $
      withCString "CollisionPolygon" $
        \ clsNamePtr ->
          withCString "_is_editable_3d_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon__is_editable_3d_polygon #-}

instance Method "_is_editable_3d_polygon" GodotCollisionPolygon
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon__is_editable_3d_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRayCast = GodotRayCast GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotRayCast where
        type BaseClass GodotRayCast = GodotSpatial
        super = coerce
bindRayCast_set_enabled
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_set_enabled #-}

instance Method "set_enabled" GodotRayCast (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_set_enabled (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_is_enabled
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_is_enabled #-}

instance Method "is_enabled" GodotRayCast (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_is_enabled (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_set_cast_to
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "set_cast_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_set_cast_to #-}

instance Method "set_cast_to" GodotRayCast (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_set_cast_to (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_cast_to
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_cast_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_cast_to #-}

instance Method "get_cast_to" GodotRayCast (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_cast_to (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_is_colliding
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "is_colliding" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_is_colliding #-}

instance Method "is_colliding" GodotRayCast (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_is_colliding (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_force_raycast_update
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "force_raycast_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_force_raycast_update #-}

instance Method "force_raycast_update" GodotRayCast (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_force_raycast_update
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_collider
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_collider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_collider #-}

instance Method "get_collider" GodotRayCast (IO GodotObject) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_collider (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_collider_shape
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_collider_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_collider_shape #-}

instance Method "get_collider_shape" GodotRayCast (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_collider_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_collision_point
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_collision_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_collision_point #-}

instance Method "get_collision_point" GodotRayCast
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_collision_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_collision_normal
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_collision_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_collision_normal #-}

instance Method "get_collision_normal" GodotRayCast
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_collision_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_add_exception_rid
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "add_exception_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_add_exception_rid #-}

instance Method "add_exception_rid" GodotRayCast
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_add_exception_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_add_exception
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "add_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_add_exception #-}

instance Method "add_exception" GodotRayCast (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_add_exception (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_remove_exception_rid
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "remove_exception_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_remove_exception_rid #-}

instance Method "remove_exception_rid" GodotRayCast
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_remove_exception_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_remove_exception
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "remove_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_remove_exception #-}

instance Method "remove_exception" GodotRayCast
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_remove_exception (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_clear_exceptions
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "clear_exceptions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_clear_exceptions #-}

instance Method "clear_exceptions" GodotRayCast (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_clear_exceptions (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_set_collision_mask
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_set_collision_mask #-}

instance Method "set_collision_mask" GodotRayCast (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_set_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_collision_mask
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_collision_mask #-}

instance Method "get_collision_mask" GodotRayCast (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_set_collision_mask_bit
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotRayCast
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_collision_mask_bit
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotRayCast
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_set_exclude_parent_body
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "set_exclude_parent_body" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_set_exclude_parent_body #-}

instance Method "set_exclude_parent_body" GodotRayCast
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_set_exclude_parent_body
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_get_exclude_parent_body
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "get_exclude_parent_body" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_get_exclude_parent_body #-}

instance Method "get_exclude_parent_body" GodotRayCast (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_get_exclude_parent_body
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_set_collide_with_areas
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "set_collide_with_areas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_set_collide_with_areas #-}

instance Method "set_collide_with_areas" GodotRayCast
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_set_collide_with_areas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_is_collide_with_areas_enabled
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "is_collide_with_areas_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_is_collide_with_areas_enabled #-}

instance Method "is_collide_with_areas_enabled" GodotRayCast
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_is_collide_with_areas_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_set_collide_with_bodies
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "set_collide_with_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_set_collide_with_bodies #-}

instance Method "set_collide_with_bodies" GodotRayCast
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_set_collide_with_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast_is_collide_with_bodies_enabled
  = unsafePerformIO $
      withCString "RayCast" $
        \ clsNamePtr ->
          withCString "is_collide_with_bodies_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast_is_collide_with_bodies_enabled #-}

instance Method "is_collide_with_bodies_enabled" GodotRayCast
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast_is_collide_with_bodies_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMultiMeshInstance = GodotMultiMeshInstance GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotMultiMeshInstance where
        type BaseClass GodotMultiMeshInstance = GodotGeometryInstance
        super = coerce
bindMultiMeshInstance_set_multimesh
  = unsafePerformIO $
      withCString "MultiMeshInstance" $
        \ clsNamePtr ->
          withCString "set_multimesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMeshInstance_set_multimesh #-}

instance Method "set_multimesh" GodotMultiMeshInstance
           (GodotMultiMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMeshInstance_set_multimesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMeshInstance_get_multimesh
  = unsafePerformIO $
      withCString "MultiMeshInstance" $
        \ clsNamePtr ->
          withCString "get_multimesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMeshInstance_get_multimesh #-}

instance Method "get_multimesh" GodotMultiMeshInstance
           (IO GodotMultiMesh)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMeshInstance_get_multimesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMultiMesh = GodotMultiMesh GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotMultiMesh where
        type BaseClass GodotMultiMesh = GodotResource
        super = coerce
bindMultiMesh_set_mesh
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_mesh #-}

instance Method "set_mesh" GodotMultiMesh (GodotMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_mesh (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_mesh
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_mesh #-}

instance Method "get_mesh" GodotMultiMesh (IO GodotMesh) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_mesh (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_set_color_format
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_color_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_color_format #-}

instance Method "set_color_format" GodotMultiMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_color_format (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_color_format
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_color_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_color_format #-}

instance Method "get_color_format" GodotMultiMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_color_format (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_set_custom_data_format
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_custom_data_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_custom_data_format #-}

instance Method "set_custom_data_format" GodotMultiMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_custom_data_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_custom_data_format
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_custom_data_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_custom_data_format #-}

instance Method "get_custom_data_format" GodotMultiMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_custom_data_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_set_transform_format
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_transform_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_transform_format #-}

instance Method "set_transform_format" GodotMultiMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_transform_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_transform_format
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_transform_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_transform_format #-}

instance Method "get_transform_format" GodotMultiMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_transform_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_set_instance_count
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_instance_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_instance_count #-}

instance Method "set_instance_count" GodotMultiMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_instance_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_instance_count
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_instance_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_instance_count #-}

instance Method "get_instance_count" GodotMultiMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_instance_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_set_instance_transform
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_instance_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_instance_transform #-}

instance Method "set_instance_transform" GodotMultiMesh
           (Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_instance_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_instance_transform
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_instance_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_instance_transform #-}

instance Method "get_instance_transform" GodotMultiMesh
           (Int -> IO GodotTransform)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_instance_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_set_instance_color
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_instance_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_instance_color #-}

instance Method "set_instance_color" GodotMultiMesh
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_instance_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_instance_color
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_instance_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_instance_color #-}

instance Method "get_instance_color" GodotMultiMesh
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_instance_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_set_instance_custom_data
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "set_instance_custom_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_set_instance_custom_data #-}

instance Method "set_instance_custom_data" GodotMultiMesh
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_set_instance_custom_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_instance_custom_data
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_instance_custom_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_instance_custom_data #-}

instance Method "get_instance_custom_data" GodotMultiMesh
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_instance_custom_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh_get_aabb
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "get_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh_get_aabb #-}

instance Method "get_aabb" GodotMultiMesh (IO GodotAabb) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh_get_aabb (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh__set_transform_array
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "_set_transform_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh__set_transform_array #-}

instance Method "_set_transform_array" GodotMultiMesh
           (GodotPoolVector3Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh__set_transform_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh__get_transform_array
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "_get_transform_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh__get_transform_array #-}

instance Method "_get_transform_array" GodotMultiMesh
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh__get_transform_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh__set_color_array
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "_set_color_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh__set_color_array #-}

instance Method "_set_color_array" GodotMultiMesh
           (GodotPoolColorArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh__set_color_array (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh__get_color_array
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "_get_color_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh__get_color_array #-}

instance Method "_get_color_array" GodotMultiMesh
           (IO GodotPoolColorArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh__get_color_array (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh__set_custom_data_array
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "_set_custom_data_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh__set_custom_data_array #-}

instance Method "_set_custom_data_array" GodotMultiMesh
           (GodotPoolColorArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh__set_custom_data_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMultiMesh__get_custom_data_array
  = unsafePerformIO $
      withCString "MultiMesh" $
        \ clsNamePtr ->
          withCString "_get_custom_data_array" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMultiMesh__get_custom_data_array #-}

instance Method "_get_custom_data_array" GodotMultiMesh
           (IO GodotPoolColorArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMultiMesh__get_custom_data_array
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCurve3D = GodotCurve3D GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotCurve3D where
        type BaseClass GodotCurve3D = GodotResource
        super = coerce
bindCurve3D_get_point_count
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_point_count #-}

instance Method "get_point_count" GodotCurve3D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_point_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_add_point
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "add_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_add_point #-}

instance Method "add_point" GodotCurve3D
           (GodotVector3 -> GodotVector3 -> GodotVector3 -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_add_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_set_point_position
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "set_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_set_point_position #-}

instance Method "set_point_position" GodotCurve3D
           (Int -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_set_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_point_position
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_point_position #-}

instance Method "get_point_position" GodotCurve3D
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_set_point_tilt
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "set_point_tilt" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_set_point_tilt #-}

instance Method "set_point_tilt" GodotCurve3D
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_set_point_tilt (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_point_tilt
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_point_tilt" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_point_tilt #-}

instance Method "get_point_tilt" GodotCurve3D (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_point_tilt (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_set_point_in
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "set_point_in" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_set_point_in #-}

instance Method "set_point_in" GodotCurve3D
           (Int -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_set_point_in (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_point_in
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_point_in" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_point_in #-}

instance Method "get_point_in" GodotCurve3D
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_point_in (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_set_point_out
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "set_point_out" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_set_point_out #-}

instance Method "set_point_out" GodotCurve3D
           (Int -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_set_point_out (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_point_out
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_point_out" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_point_out #-}

instance Method "get_point_out" GodotCurve3D
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_point_out (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_remove_point
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "remove_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_remove_point #-}

instance Method "remove_point" GodotCurve3D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_remove_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_clear_points
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "clear_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_clear_points #-}

instance Method "clear_points" GodotCurve3D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_clear_points (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_interpolate
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "interpolate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_interpolate #-}

instance Method "interpolate" GodotCurve3D
           (Int -> Float -> IO GodotVector3)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_interpolate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_interpolatef
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "interpolatef" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_interpolatef #-}

instance Method "interpolatef" GodotCurve3D
           (Float -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_interpolatef (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_set_bake_interval
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "set_bake_interval" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_set_bake_interval #-}

instance Method "set_bake_interval" GodotCurve3D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_set_bake_interval (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_bake_interval
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_bake_interval" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_bake_interval #-}

instance Method "get_bake_interval" GodotCurve3D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_bake_interval (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_set_up_vector_enabled
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "set_up_vector_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_set_up_vector_enabled #-}

instance Method "set_up_vector_enabled" GodotCurve3D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_set_up_vector_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_is_up_vector_enabled
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "is_up_vector_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_is_up_vector_enabled #-}

instance Method "is_up_vector_enabled" GodotCurve3D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_is_up_vector_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_baked_length
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_baked_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_baked_length #-}

instance Method "get_baked_length" GodotCurve3D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_baked_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_interpolate_baked
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "interpolate_baked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_interpolate_baked #-}

instance Method "interpolate_baked" GodotCurve3D
           (Float -> Bool -> IO GodotVector3)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_interpolate_baked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_interpolate_baked_up_vector
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "interpolate_baked_up_vector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_interpolate_baked_up_vector #-}

instance Method "interpolate_baked_up_vector" GodotCurve3D
           (Float -> Bool -> IO GodotVector3)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_interpolate_baked_up_vector
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_baked_points
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_baked_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_baked_points #-}

instance Method "get_baked_points" GodotCurve3D
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_baked_points (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_baked_tilts
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_baked_tilts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_baked_tilts #-}

instance Method "get_baked_tilts" GodotCurve3D
           (IO GodotPoolRealArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_baked_tilts (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_baked_up_vectors
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_baked_up_vectors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_baked_up_vectors #-}

instance Method "get_baked_up_vectors" GodotCurve3D
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_baked_up_vectors
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_closest_point
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_closest_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_closest_point #-}

instance Method "get_closest_point" GodotCurve3D
           (GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_closest_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_get_closest_offset
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "get_closest_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_get_closest_offset #-}

instance Method "get_closest_offset" GodotCurve3D
           (GodotVector3 -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_get_closest_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D_tessellate
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "tessellate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D_tessellate #-}

instance Method "tessellate" GodotCurve3D
           (Int -> Float -> IO GodotPoolVector3Array)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D_tessellate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D__get_data
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D__get_data #-}

instance Method "_get_data" GodotCurve3D (IO GodotDictionary) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D__get_data (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve3D__set_data
  = unsafePerformIO $
      withCString "Curve3D" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve3D__set_data #-}

instance Method "_set_data" GodotCurve3D (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve3D__set_data (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPath = GodotPath GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotPath where
        type BaseClass GodotPath = GodotSpatial
        super = coerce
bindPath_set_curve
  = unsafePerformIO $
      withCString "Path" $
        \ clsNamePtr ->
          withCString "set_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPath_set_curve #-}

instance Method "set_curve" GodotPath (GodotCurve3D -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPath_set_curve (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPath_get_curve
  = unsafePerformIO $
      withCString "Path" $
        \ clsNamePtr ->
          withCString "get_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPath_get_curve #-}

instance Method "get_curve" GodotPath (IO GodotCurve3D) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPath_get_curve (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPath__curve_changed
  = unsafePerformIO $
      withCString "Path" $
        \ clsNamePtr ->
          withCString "_curve_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPath__curve_changed #-}

instance Method "_curve_changed" GodotPath (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPath__curve_changed (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPathFollow = GodotPathFollow GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotPathFollow where
        type BaseClass GodotPathFollow = GodotSpatial
        super = coerce
bindPathFollow_set_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_set_offset #-}

instance Method "set_offset" GodotPathFollow (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_set_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_get_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_get_offset #-}

instance Method "get_offset" GodotPathFollow (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_get_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_set_h_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "set_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_set_h_offset #-}

instance Method "set_h_offset" GodotPathFollow (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_set_h_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_get_h_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "get_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_get_h_offset #-}

instance Method "get_h_offset" GodotPathFollow (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_get_h_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_set_v_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "set_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_set_v_offset #-}

instance Method "set_v_offset" GodotPathFollow (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_set_v_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_get_v_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "get_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_get_v_offset #-}

instance Method "get_v_offset" GodotPathFollow (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_get_v_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_set_unit_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "set_unit_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_set_unit_offset #-}

instance Method "set_unit_offset" GodotPathFollow (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_set_unit_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_get_unit_offset
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "get_unit_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_get_unit_offset #-}

instance Method "get_unit_offset" GodotPathFollow (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_get_unit_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_set_rotation_mode
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "set_rotation_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_set_rotation_mode #-}

instance Method "set_rotation_mode" GodotPathFollow (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_set_rotation_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_get_rotation_mode
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "get_rotation_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_get_rotation_mode #-}

instance Method "get_rotation_mode" GodotPathFollow (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_get_rotation_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_set_cubic_interpolation
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "set_cubic_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_set_cubic_interpolation #-}

instance Method "set_cubic_interpolation" GodotPathFollow
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_set_cubic_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_get_cubic_interpolation
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "get_cubic_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_get_cubic_interpolation #-}

instance Method "get_cubic_interpolation" GodotPathFollow (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_get_cubic_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_set_loop
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "set_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_set_loop #-}

instance Method "set_loop" GodotPathFollow (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_set_loop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow_has_loop
  = unsafePerformIO $
      withCString "PathFollow" $
        \ clsNamePtr ->
          withCString "has_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow_has_loop #-}

instance Method "has_loop" GodotPathFollow (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow_has_loop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotOrientedPathFollow = GodotOrientedPathFollow GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotOrientedPathFollow where
        type BaseClass GodotOrientedPathFollow = GodotSpatial
        super = coerce
bindOrientedPathFollow_set_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_set_offset #-}

instance Method "set_offset" GodotOrientedPathFollow
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_set_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_get_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_get_offset #-}

instance Method "get_offset" GodotOrientedPathFollow (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_get_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_set_h_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "set_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_set_h_offset #-}

instance Method "set_h_offset" GodotOrientedPathFollow
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_set_h_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_get_h_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "get_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_get_h_offset #-}

instance Method "get_h_offset" GodotOrientedPathFollow (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_get_h_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_set_v_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "set_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_set_v_offset #-}

instance Method "set_v_offset" GodotOrientedPathFollow
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_set_v_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_get_v_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "get_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_get_v_offset #-}

instance Method "get_v_offset" GodotOrientedPathFollow (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_get_v_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_set_unit_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "set_unit_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_set_unit_offset #-}

instance Method "set_unit_offset" GodotOrientedPathFollow
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_set_unit_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_get_unit_offset
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "get_unit_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_get_unit_offset #-}

instance Method "get_unit_offset" GodotOrientedPathFollow
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_get_unit_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_set_cubic_interpolation
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "set_cubic_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_set_cubic_interpolation #-}

instance Method "set_cubic_interpolation" GodotOrientedPathFollow
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindOrientedPathFollow_set_cubic_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_get_cubic_interpolation
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "get_cubic_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_get_cubic_interpolation #-}

instance Method "get_cubic_interpolation" GodotOrientedPathFollow
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindOrientedPathFollow_get_cubic_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_set_loop
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "set_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_set_loop #-}

instance Method "set_loop" GodotOrientedPathFollow (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_set_loop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOrientedPathFollow_has_loop
  = unsafePerformIO $
      withCString "OrientedPathFollow" $
        \ clsNamePtr ->
          withCString "has_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOrientedPathFollow_has_loop #-}

instance Method "has_loop" GodotOrientedPathFollow (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOrientedPathFollow_has_loop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisibilityNotifier = GodotVisibilityNotifier GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotVisibilityNotifier where
        type BaseClass GodotVisibilityNotifier = GodotSpatial
        super = coerce
bindVisibilityNotifier_set_aabb
  = unsafePerformIO $
      withCString "VisibilityNotifier" $
        \ clsNamePtr ->
          withCString "set_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityNotifier_set_aabb #-}

instance Method "set_aabb" GodotVisibilityNotifier
           (GodotAabb -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityNotifier_set_aabb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityNotifier_get_aabb
  = unsafePerformIO $
      withCString "VisibilityNotifier" $
        \ clsNamePtr ->
          withCString "get_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityNotifier_get_aabb #-}

instance Method "get_aabb" GodotVisibilityNotifier (IO GodotAabb)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityNotifier_get_aabb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityNotifier_is_on_screen
  = unsafePerformIO $
      withCString "VisibilityNotifier" $
        \ clsNamePtr ->
          withCString "is_on_screen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityNotifier_is_on_screen #-}

instance Method "is_on_screen" GodotVisibilityNotifier (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityNotifier_is_on_screen
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisibilityEnabler = GodotVisibilityEnabler GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotVisibilityEnabler where
        type BaseClass GodotVisibilityEnabler = GodotVisibilityNotifier
        super = coerce
bindVisibilityEnabler_set_enabler
  = unsafePerformIO $
      withCString "VisibilityEnabler" $
        \ clsNamePtr ->
          withCString "set_enabler" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityEnabler_set_enabler #-}

instance Method "set_enabler" GodotVisibilityEnabler
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityEnabler_set_enabler
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityEnabler_is_enabler_enabled
  = unsafePerformIO $
      withCString "VisibilityEnabler" $
        \ clsNamePtr ->
          withCString "is_enabler_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityEnabler_is_enabler_enabled #-}

instance Method "is_enabler_enabled" GodotVisibilityEnabler
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityEnabler_is_enabler_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityEnabler__node_removed
  = unsafePerformIO $
      withCString "VisibilityEnabler" $
        \ clsNamePtr ->
          withCString "_node_removed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityEnabler__node_removed #-}

instance Method "_node_removed" GodotVisibilityEnabler
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityEnabler__node_removed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWorldEnvironment = GodotWorldEnvironment GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotWorldEnvironment where
        type BaseClass GodotWorldEnvironment = GodotNode
        super = coerce
bindWorldEnvironment_set_environment
  = unsafePerformIO $
      withCString "WorldEnvironment" $
        \ clsNamePtr ->
          withCString "set_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorldEnvironment_set_environment #-}

instance Method "set_environment" GodotWorldEnvironment
           (GodotEnvironment -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorldEnvironment_set_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWorldEnvironment_get_environment
  = unsafePerformIO $
      withCString "WorldEnvironment" $
        \ clsNamePtr ->
          withCString "get_environment" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWorldEnvironment_get_environment #-}

instance Method "get_environment" GodotWorldEnvironment
           (IO GodotEnvironment)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWorldEnvironment_get_environment
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRemoteTransform = GodotRemoteTransform GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotRemoteTransform where
        type BaseClass GodotRemoteTransform = GodotSpatial
        super = coerce
bindRemoteTransform_set_remote_node
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "set_remote_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_set_remote_node #-}

instance Method "set_remote_node" GodotRemoteTransform
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_set_remote_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_get_remote_node
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "get_remote_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_get_remote_node #-}

instance Method "get_remote_node" GodotRemoteTransform
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_get_remote_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_set_use_global_coordinates
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "set_use_global_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_set_use_global_coordinates #-}

instance Method "set_use_global_coordinates" GodotRemoteTransform
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRemoteTransform_set_use_global_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_get_use_global_coordinates
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "get_use_global_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_get_use_global_coordinates #-}

instance Method "get_use_global_coordinates" GodotRemoteTransform
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRemoteTransform_get_use_global_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_set_update_position
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "set_update_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_set_update_position #-}

instance Method "set_update_position" GodotRemoteTransform
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_set_update_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_get_update_position
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "get_update_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_get_update_position #-}

instance Method "get_update_position" GodotRemoteTransform
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_get_update_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_set_update_rotation
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "set_update_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_set_update_rotation #-}

instance Method "set_update_rotation" GodotRemoteTransform
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_set_update_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_get_update_rotation
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "get_update_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_get_update_rotation #-}

instance Method "get_update_rotation" GodotRemoteTransform
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_get_update_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_set_update_scale
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "set_update_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_set_update_scale #-}

instance Method "set_update_scale" GodotRemoteTransform
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_set_update_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform_get_update_scale
  = unsafePerformIO $
      withCString "RemoteTransform" $
        \ clsNamePtr ->
          withCString "get_update_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform_get_update_scale #-}

instance Method "get_update_scale" GodotRemoteTransform (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform_get_update_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotJoint = GodotJoint GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotJoint where
        type BaseClass GodotJoint = GodotSpatial
        super = coerce
bindJoint_set_node_a
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "set_node_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_set_node_a #-}

instance Method "set_node_a" GodotJoint (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_set_node_a (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint_get_node_a
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "get_node_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_get_node_a #-}

instance Method "get_node_a" GodotJoint (IO GodotNodePath) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_get_node_a (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint_set_node_b
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "set_node_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_set_node_b #-}

instance Method "set_node_b" GodotJoint (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_set_node_b (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint_get_node_b
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "get_node_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_get_node_b #-}

instance Method "get_node_b" GodotJoint (IO GodotNodePath) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_get_node_b (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint_set_solver_priority
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "set_solver_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_set_solver_priority #-}

instance Method "set_solver_priority" GodotJoint (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_set_solver_priority (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint_get_solver_priority
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "get_solver_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_get_solver_priority #-}

instance Method "get_solver_priority" GodotJoint (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_get_solver_priority (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint_set_exclude_nodes_from_collision
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "set_exclude_nodes_from_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_set_exclude_nodes_from_collision #-}

instance Method "set_exclude_nodes_from_collision" GodotJoint
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_set_exclude_nodes_from_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint_get_exclude_nodes_from_collision
  = unsafePerformIO $
      withCString "Joint" $
        \ clsNamePtr ->
          withCString "get_exclude_nodes_from_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint_get_exclude_nodes_from_collision #-}

instance Method "get_exclude_nodes_from_collision" GodotJoint
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint_get_exclude_nodes_from_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPinJoint = GodotPinJoint GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotPinJoint where
        type BaseClass GodotPinJoint = GodotJoint
        super = coerce
bindPinJoint_set_param
  = unsafePerformIO $
      withCString "PinJoint" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPinJoint_set_param #-}

instance Method "set_param" GodotPinJoint (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPinJoint_set_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPinJoint_get_param
  = unsafePerformIO $
      withCString "PinJoint" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPinJoint_get_param #-}

instance Method "get_param" GodotPinJoint (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPinJoint_get_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotHingeJoint = GodotHingeJoint GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotHingeJoint where
        type BaseClass GodotHingeJoint = GodotJoint
        super = coerce
bindHingeJoint_set_param
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint_set_param #-}

instance Method "set_param" GodotHingeJoint (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint_set_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHingeJoint_get_param
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint_get_param #-}

instance Method "get_param" GodotHingeJoint (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint_get_param (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHingeJoint_set_flag
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "set_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint_set_flag #-}

instance Method "set_flag" GodotHingeJoint (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint_set_flag (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHingeJoint_get_flag
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "get_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint_get_flag #-}

instance Method "get_flag" GodotHingeJoint (Int -> IO Bool) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint_get_flag (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHingeJoint__set_upper_limit
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "_set_upper_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint__set_upper_limit #-}

instance Method "_set_upper_limit" GodotHingeJoint (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint__set_upper_limit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHingeJoint__get_upper_limit
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "_get_upper_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint__get_upper_limit #-}

instance Method "_get_upper_limit" GodotHingeJoint (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint__get_upper_limit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHingeJoint__set_lower_limit
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "_set_lower_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint__set_lower_limit #-}

instance Method "_set_lower_limit" GodotHingeJoint (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint__set_lower_limit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindHingeJoint__get_lower_limit
  = unsafePerformIO $
      withCString "HingeJoint" $
        \ clsNamePtr ->
          withCString "_get_lower_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindHingeJoint__get_lower_limit #-}

instance Method "_get_lower_limit" GodotHingeJoint (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindHingeJoint__get_lower_limit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSliderJoint = GodotSliderJoint GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotSliderJoint where
        type BaseClass GodotSliderJoint = GodotJoint
        super = coerce
bindSliderJoint_set_param
  = unsafePerformIO $
      withCString "SliderJoint" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSliderJoint_set_param #-}

instance Method "set_param" GodotSliderJoint
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSliderJoint_set_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSliderJoint_get_param
  = unsafePerformIO $
      withCString "SliderJoint" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSliderJoint_get_param #-}

instance Method "get_param" GodotSliderJoint (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSliderJoint_get_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSliderJoint__set_upper_limit_angular
  = unsafePerformIO $
      withCString "SliderJoint" $
        \ clsNamePtr ->
          withCString "_set_upper_limit_angular" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSliderJoint__set_upper_limit_angular #-}

instance Method "_set_upper_limit_angular" GodotSliderJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSliderJoint__set_upper_limit_angular
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSliderJoint__get_upper_limit_angular
  = unsafePerformIO $
      withCString "SliderJoint" $
        \ clsNamePtr ->
          withCString "_get_upper_limit_angular" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSliderJoint__get_upper_limit_angular #-}

instance Method "_get_upper_limit_angular" GodotSliderJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSliderJoint__get_upper_limit_angular
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSliderJoint__set_lower_limit_angular
  = unsafePerformIO $
      withCString "SliderJoint" $
        \ clsNamePtr ->
          withCString "_set_lower_limit_angular" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSliderJoint__set_lower_limit_angular #-}

instance Method "_set_lower_limit_angular" GodotSliderJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSliderJoint__set_lower_limit_angular
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSliderJoint__get_lower_limit_angular
  = unsafePerformIO $
      withCString "SliderJoint" $
        \ clsNamePtr ->
          withCString "_get_lower_limit_angular" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSliderJoint__get_lower_limit_angular #-}

instance Method "_get_lower_limit_angular" GodotSliderJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSliderJoint__get_lower_limit_angular
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotConeTwistJoint = GodotConeTwistJoint GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotConeTwistJoint where
        type BaseClass GodotConeTwistJoint = GodotJoint
        super = coerce
bindConeTwistJoint_set_param
  = unsafePerformIO $
      withCString "ConeTwistJoint" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConeTwistJoint_set_param #-}

instance Method "set_param" GodotConeTwistJoint
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConeTwistJoint_set_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConeTwistJoint_get_param
  = unsafePerformIO $
      withCString "ConeTwistJoint" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConeTwistJoint_get_param #-}

instance Method "get_param" GodotConeTwistJoint (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConeTwistJoint_get_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConeTwistJoint__set_swing_span
  = unsafePerformIO $
      withCString "ConeTwistJoint" $
        \ clsNamePtr ->
          withCString "_set_swing_span" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConeTwistJoint__set_swing_span #-}

instance Method "_set_swing_span" GodotConeTwistJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConeTwistJoint__set_swing_span
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConeTwistJoint__get_swing_span
  = unsafePerformIO $
      withCString "ConeTwistJoint" $
        \ clsNamePtr ->
          withCString "_get_swing_span" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConeTwistJoint__get_swing_span #-}

instance Method "_get_swing_span" GodotConeTwistJoint (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConeTwistJoint__get_swing_span
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConeTwistJoint__set_twist_span
  = unsafePerformIO $
      withCString "ConeTwistJoint" $
        \ clsNamePtr ->
          withCString "_set_twist_span" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConeTwistJoint__set_twist_span #-}

instance Method "_set_twist_span" GodotConeTwistJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConeTwistJoint__set_twist_span
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConeTwistJoint__get_twist_span
  = unsafePerformIO $
      withCString "ConeTwistJoint" $
        \ clsNamePtr ->
          withCString "_get_twist_span" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConeTwistJoint__get_twist_span #-}

instance Method "_get_twist_span" GodotConeTwistJoint (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConeTwistJoint__get_twist_span
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGeneric6DOFJoint = GodotGeneric6DOFJoint GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotGeneric6DOFJoint where
        type BaseClass GodotGeneric6DOFJoint = GodotJoint
        super = coerce
bindGeneric6DOFJoint__set_angular_hi_limit_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_set_angular_hi_limit_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__set_angular_hi_limit_x #-}

instance Method "_set_angular_hi_limit_x" GodotGeneric6DOFJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__set_angular_hi_limit_x
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__get_angular_hi_limit_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_get_angular_hi_limit_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__get_angular_hi_limit_x #-}

instance Method "_get_angular_hi_limit_x" GodotGeneric6DOFJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__get_angular_hi_limit_x
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__set_angular_lo_limit_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_set_angular_lo_limit_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__set_angular_lo_limit_x #-}

instance Method "_set_angular_lo_limit_x" GodotGeneric6DOFJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__set_angular_lo_limit_x
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__get_angular_lo_limit_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_get_angular_lo_limit_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__get_angular_lo_limit_x #-}

instance Method "_get_angular_lo_limit_x" GodotGeneric6DOFJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__get_angular_lo_limit_x
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__set_angular_hi_limit_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_set_angular_hi_limit_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__set_angular_hi_limit_y #-}

instance Method "_set_angular_hi_limit_y" GodotGeneric6DOFJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__set_angular_hi_limit_y
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__get_angular_hi_limit_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_get_angular_hi_limit_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__get_angular_hi_limit_y #-}

instance Method "_get_angular_hi_limit_y" GodotGeneric6DOFJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__get_angular_hi_limit_y
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__set_angular_lo_limit_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_set_angular_lo_limit_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__set_angular_lo_limit_y #-}

instance Method "_set_angular_lo_limit_y" GodotGeneric6DOFJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__set_angular_lo_limit_y
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__get_angular_lo_limit_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_get_angular_lo_limit_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__get_angular_lo_limit_y #-}

instance Method "_get_angular_lo_limit_y" GodotGeneric6DOFJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__get_angular_lo_limit_y
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__set_angular_hi_limit_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_set_angular_hi_limit_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__set_angular_hi_limit_z #-}

instance Method "_set_angular_hi_limit_z" GodotGeneric6DOFJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__set_angular_hi_limit_z
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__get_angular_hi_limit_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_get_angular_hi_limit_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__get_angular_hi_limit_z #-}

instance Method "_get_angular_hi_limit_z" GodotGeneric6DOFJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__get_angular_hi_limit_z
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__set_angular_lo_limit_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_set_angular_lo_limit_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__set_angular_lo_limit_z #-}

instance Method "_set_angular_lo_limit_z" GodotGeneric6DOFJoint
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__set_angular_lo_limit_z
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint__get_angular_lo_limit_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "_get_angular_lo_limit_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint__get_angular_lo_limit_z #-}

instance Method "_get_angular_lo_limit_z" GodotGeneric6DOFJoint
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint__get_angular_lo_limit_z
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_set_param_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "set_param_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_set_param_x #-}

instance Method "set_param_x" GodotGeneric6DOFJoint
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_set_param_x
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_get_param_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "get_param_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_get_param_x #-}

instance Method "get_param_x" GodotGeneric6DOFJoint
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_get_param_x
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_set_param_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "set_param_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_set_param_y #-}

instance Method "set_param_y" GodotGeneric6DOFJoint
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_set_param_y
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_get_param_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "get_param_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_get_param_y #-}

instance Method "get_param_y" GodotGeneric6DOFJoint
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_get_param_y
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_set_param_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "set_param_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_set_param_z #-}

instance Method "set_param_z" GodotGeneric6DOFJoint
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_set_param_z
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_get_param_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "get_param_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_get_param_z #-}

instance Method "get_param_z" GodotGeneric6DOFJoint
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_get_param_z
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_set_flag_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "set_flag_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_set_flag_x #-}

instance Method "set_flag_x" GodotGeneric6DOFJoint
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_set_flag_x (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_get_flag_x
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "get_flag_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_get_flag_x #-}

instance Method "get_flag_x" GodotGeneric6DOFJoint (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_get_flag_x (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_set_flag_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "set_flag_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_set_flag_y #-}

instance Method "set_flag_y" GodotGeneric6DOFJoint
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_set_flag_y (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_get_flag_y
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "get_flag_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_get_flag_y #-}

instance Method "get_flag_y" GodotGeneric6DOFJoint (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_get_flag_y (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_set_flag_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "set_flag_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_set_flag_z #-}

instance Method "set_flag_z" GodotGeneric6DOFJoint
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_set_flag_z (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGeneric6DOFJoint_get_flag_z
  = unsafePerformIO $
      withCString "Generic6DOFJoint" $
        \ clsNamePtr ->
          withCString "get_flag_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGeneric6DOFJoint_get_flag_z #-}

instance Method "get_flag_z" GodotGeneric6DOFJoint (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGeneric6DOFJoint_get_flag_z (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMeshLibrary = GodotMeshLibrary GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotMeshLibrary where
        type BaseClass GodotMeshLibrary = GodotResource
        super = coerce
bindMeshLibrary_create_item
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "create_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_create_item #-}

instance Method "create_item" GodotMeshLibrary (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_create_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_set_item_name
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "set_item_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_set_item_name #-}

instance Method "set_item_name" GodotMeshLibrary
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_set_item_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_set_item_mesh
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "set_item_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_set_item_mesh #-}

instance Method "set_item_mesh" GodotMeshLibrary
           (Int -> GodotMesh -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_set_item_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_set_item_navmesh
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "set_item_navmesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_set_item_navmesh #-}

instance Method "set_item_navmesh" GodotMeshLibrary
           (Int -> GodotNavigationMesh -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_set_item_navmesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_set_item_shapes
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "set_item_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_set_item_shapes #-}

instance Method "set_item_shapes" GodotMeshLibrary
           (Int -> GodotArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_set_item_shapes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_set_item_preview
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "set_item_preview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_set_item_preview #-}

instance Method "set_item_preview" GodotMeshLibrary
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_set_item_preview
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_get_item_name
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "get_item_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_get_item_name #-}

instance Method "get_item_name" GodotMeshLibrary
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_get_item_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_get_item_mesh
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "get_item_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_get_item_mesh #-}

instance Method "get_item_mesh" GodotMeshLibrary
           (Int -> IO GodotMesh)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_get_item_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_get_item_navmesh
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "get_item_navmesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_get_item_navmesh #-}

instance Method "get_item_navmesh" GodotMeshLibrary
           (Int -> IO GodotNavigationMesh)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_get_item_navmesh
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_get_item_shapes
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "get_item_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_get_item_shapes #-}

instance Method "get_item_shapes" GodotMeshLibrary
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_get_item_shapes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_get_item_preview
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "get_item_preview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_get_item_preview #-}

instance Method "get_item_preview" GodotMeshLibrary
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_get_item_preview
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_remove_item
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "remove_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_remove_item #-}

instance Method "remove_item" GodotMeshLibrary (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_remove_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_find_item_by_name
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "find_item_by_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_find_item_by_name #-}

instance Method "find_item_by_name" GodotMeshLibrary
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_find_item_by_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_clear
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_clear #-}

instance Method "clear" GodotMeshLibrary (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_get_item_list
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "get_item_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_get_item_list #-}

instance Method "get_item_list" GodotMeshLibrary
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_get_item_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshLibrary_get_last_unused_item_id
  = unsafePerformIO $
      withCString "MeshLibrary" $
        \ clsNamePtr ->
          withCString "get_last_unused_item_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshLibrary_get_last_unused_item_id #-}

instance Method "get_last_unused_item_id" GodotMeshLibrary (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshLibrary_get_last_unused_item_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotShader = GodotShader GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotShader where
        type BaseClass GodotShader = GodotResource
        super = coerce
bindShader_get_mode
  = unsafePerformIO $
      withCString "Shader" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShader_get_mode #-}

instance Method "get_mode" GodotShader (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShader_get_mode (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShader_set_code
  = unsafePerformIO $
      withCString "Shader" $
        \ clsNamePtr ->
          withCString "set_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShader_set_code #-}

instance Method "set_code" GodotShader (GodotString -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShader_set_code (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShader_get_code
  = unsafePerformIO $
      withCString "Shader" $
        \ clsNamePtr ->
          withCString "get_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShader_get_code #-}

instance Method "get_code" GodotShader (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShader_get_code (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShader_set_default_texture_param
  = unsafePerformIO $
      withCString "Shader" $
        \ clsNamePtr ->
          withCString "set_default_texture_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShader_set_default_texture_param #-}

instance Method "set_default_texture_param" GodotShader
           (GodotString -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShader_set_default_texture_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShader_get_default_texture_param
  = unsafePerformIO $
      withCString "Shader" $
        \ clsNamePtr ->
          withCString "get_default_texture_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShader_get_default_texture_param #-}

instance Method "get_default_texture_param" GodotShader
           (GodotString -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShader_get_default_texture_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShader_has_param
  = unsafePerformIO $
      withCString "Shader" $
        \ clsNamePtr ->
          withCString "has_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShader_has_param #-}

instance Method "has_param" GodotShader (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShader_has_param (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShader = GodotVisualShader GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotVisualShader where
        type BaseClass GodotVisualShader = GodotShader
        super = coerce
bindVisualShader_set_mode
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_set_mode #-}

instance Method "set_mode" GodotVisualShader (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_set_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_add_node
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "add_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_add_node #-}

instance Method "add_node" GodotVisualShader
           (Int -> GodotVisualShaderNode -> GodotVector2 -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_add_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_set_node_position
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "set_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_set_node_position #-}

instance Method "set_node_position" GodotVisualShader
           (Int -> Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_set_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_get_node
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "get_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_get_node #-}

instance Method "get_node" GodotVisualShader
           (Int -> Int -> IO GodotVisualShaderNode)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_get_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_get_node_position
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "get_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_get_node_position #-}

instance Method "get_node_position" GodotVisualShader
           (Int -> Int -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_get_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_get_node_list
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "get_node_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_get_node_list #-}

instance Method "get_node_list" GodotVisualShader
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_get_node_list (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_get_valid_node_id
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "get_valid_node_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_get_valid_node_id #-}

instance Method "get_valid_node_id" GodotVisualShader
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_get_valid_node_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_remove_node
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "remove_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_remove_node #-}

instance Method "remove_node" GodotVisualShader
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_remove_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_is_node_connection
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "is_node_connection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_is_node_connection #-}

instance Method "is_node_connection" GodotVisualShader
           (Int -> Int -> Int -> Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_is_node_connection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_can_connect_nodes
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "can_connect_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_can_connect_nodes #-}

instance Method "can_connect_nodes" GodotVisualShader
           (Int -> Int -> Int -> Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_can_connect_nodes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_connect_nodes
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "connect_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_connect_nodes #-}

instance Method "connect_nodes" GodotVisualShader
           (Int -> Int -> Int -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_connect_nodes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_disconnect_nodes
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "disconnect_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_disconnect_nodes #-}

instance Method "disconnect_nodes" GodotVisualShader
           (Int -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_disconnect_nodes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_get_node_connections
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "get_node_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_get_node_connections #-}

instance Method "get_node_connections" GodotVisualShader
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_get_node_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_set_graph_offset
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "set_graph_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_set_graph_offset #-}

instance Method "set_graph_offset" GodotVisualShader
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_set_graph_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader_get_graph_offset
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "get_graph_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader_get_graph_offset #-}

instance Method "get_graph_offset" GodotVisualShader
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader_get_graph_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader__queue_update
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "_queue_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader__queue_update #-}

instance Method "_queue_update" GodotVisualShader (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader__queue_update (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader__update_shader
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "_update_shader" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader__update_shader #-}

instance Method "_update_shader" GodotVisualShader (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader__update_shader (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShader__input_type_changed
  = unsafePerformIO $
      withCString "VisualShader" $
        \ clsNamePtr ->
          withCString "_input_type_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShader__input_type_changed #-}

instance Method "_input_type_changed" GodotVisualShader
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShader__input_type_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNode = GodotVisualShaderNode GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNode where
        type BaseClass GodotVisualShaderNode = GodotResource
        super = coerce
bindVisualShaderNode_set_output_port_for_preview
  = unsafePerformIO $
      withCString "VisualShaderNode" $
        \ clsNamePtr ->
          withCString "set_output_port_for_preview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNode_set_output_port_for_preview #-}

instance Method "set_output_port_for_preview" GodotVisualShaderNode
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNode_set_output_port_for_preview
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNode_get_output_port_for_preview
  = unsafePerformIO $
      withCString "VisualShaderNode" $
        \ clsNamePtr ->
          withCString "get_output_port_for_preview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNode_get_output_port_for_preview #-}

instance Method "get_output_port_for_preview" GodotVisualShaderNode
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNode_get_output_port_for_preview
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNode_set_input_port_default_value
  = unsafePerformIO $
      withCString "VisualShaderNode" $
        \ clsNamePtr ->
          withCString "set_input_port_default_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNode_set_input_port_default_value #-}

instance Method "set_input_port_default_value"
           GodotVisualShaderNode
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNode_set_input_port_default_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNode_get_input_port_default_value
  = unsafePerformIO $
      withCString "VisualShaderNode" $
        \ clsNamePtr ->
          withCString "get_input_port_default_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNode_get_input_port_default_value #-}

instance Method "get_input_port_default_value"
           GodotVisualShaderNode
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNode_get_input_port_default_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNode__set_default_input_values
  = unsafePerformIO $
      withCString "VisualShaderNode" $
        \ clsNamePtr ->
          withCString "_set_default_input_values" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNode__set_default_input_values #-}

instance Method "_set_default_input_values" GodotVisualShaderNode
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNode__set_default_input_values
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNode__get_default_input_values
  = unsafePerformIO $
      withCString "VisualShaderNode" $
        \ clsNamePtr ->
          withCString "_get_default_input_values" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNode__get_default_input_values #-}

instance Method "_get_default_input_values" GodotVisualShaderNode
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNode__get_default_input_values
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeInput = GodotVisualShaderNodeInput GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeInput where
        type BaseClass GodotVisualShaderNodeInput = GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeInput_set_input_name
  = unsafePerformIO $
      withCString "VisualShaderNodeInput" $
        \ clsNamePtr ->
          withCString "set_input_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeInput_set_input_name #-}

instance Method "set_input_name" GodotVisualShaderNodeInput
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeInput_set_input_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeInput_get_input_name
  = unsafePerformIO $
      withCString "VisualShaderNodeInput" $
        \ clsNamePtr ->
          withCString "get_input_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeInput_get_input_name #-}

instance Method "get_input_name" GodotVisualShaderNodeInput
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeInput_get_input_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeOutput = GodotVisualShaderNodeOutput GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeOutput where
        type BaseClass GodotVisualShaderNodeOutput = GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeScalarConstant = GodotVisualShaderNodeScalarConstant GodotObject
                                                deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeScalarConstant where
        type BaseClass GodotVisualShaderNodeScalarConstant =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeScalarConstant_set_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeScalarConstant" $
        \ clsNamePtr ->
          withCString "set_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeScalarConstant_set_constant #-}

instance Method "set_constant" GodotVisualShaderNodeScalarConstant
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeScalarConstant_set_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeScalarConstant_get_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeScalarConstant" $
        \ clsNamePtr ->
          withCString "get_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeScalarConstant_get_constant #-}

instance Method "get_constant" GodotVisualShaderNodeScalarConstant
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeScalarConstant_get_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeColorConstant = GodotVisualShaderNodeColorConstant GodotObject
                                               deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeColorConstant where
        type BaseClass GodotVisualShaderNodeColorConstant =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeColorConstant_set_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeColorConstant" $
        \ clsNamePtr ->
          withCString "set_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeColorConstant_set_constant #-}

instance Method "set_constant" GodotVisualShaderNodeColorConstant
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeColorConstant_set_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeColorConstant_get_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeColorConstant" $
        \ clsNamePtr ->
          withCString "get_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeColorConstant_get_constant #-}

instance Method "get_constant" GodotVisualShaderNodeColorConstant
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeColorConstant_get_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeVec3Constant = GodotVisualShaderNodeVec3Constant GodotObject
                                              deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVec3Constant where
        type BaseClass GodotVisualShaderNodeVec3Constant =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeVec3Constant_set_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeVec3Constant" $
        \ clsNamePtr ->
          withCString "set_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeVec3Constant_set_constant #-}

instance Method "set_constant" GodotVisualShaderNodeVec3Constant
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeVec3Constant_set_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeVec3Constant_get_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeVec3Constant" $
        \ clsNamePtr ->
          withCString "get_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeVec3Constant_get_constant #-}

instance Method "get_constant" GodotVisualShaderNodeVec3Constant
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeVec3Constant_get_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeTransformConstant = GodotVisualShaderNodeTransformConstant GodotObject
                                                   deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTransformConstant where
        type BaseClass GodotVisualShaderNodeTransformConstant =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeTransformConstant_set_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeTransformConstant" $
        \ clsNamePtr ->
          withCString "set_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTransformConstant_set_constant #-}

instance Method "set_constant"
           GodotVisualShaderNodeTransformConstant
           (GodotTransform -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTransformConstant_set_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTransformConstant_get_constant
  = unsafePerformIO $
      withCString "VisualShaderNodeTransformConstant" $
        \ clsNamePtr ->
          withCString "get_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTransformConstant_get_constant #-}

instance Method "get_constant"
           GodotVisualShaderNodeTransformConstant
           (IO GodotTransform)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTransformConstant_get_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeScalarOp = GodotVisualShaderNodeScalarOp GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeScalarOp where
        type BaseClass GodotVisualShaderNodeScalarOp =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeScalarOp_set_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeScalarOp" $
        \ clsNamePtr ->
          withCString "set_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeScalarOp_set_operator #-}

instance Method "set_operator" GodotVisualShaderNodeScalarOp
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeScalarOp_set_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeScalarOp_get_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeScalarOp" $
        \ clsNamePtr ->
          withCString "get_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeScalarOp_get_operator #-}

instance Method "get_operator" GodotVisualShaderNodeScalarOp
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeScalarOp_get_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeVectorOp = GodotVisualShaderNodeVectorOp GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVectorOp where
        type BaseClass GodotVisualShaderNodeVectorOp =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeVectorOp_set_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeVectorOp" $
        \ clsNamePtr ->
          withCString "set_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeVectorOp_set_operator #-}

instance Method "set_operator" GodotVisualShaderNodeVectorOp
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeVectorOp_set_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeVectorOp_get_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeVectorOp" $
        \ clsNamePtr ->
          withCString "get_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeVectorOp_get_operator #-}

instance Method "get_operator" GodotVisualShaderNodeVectorOp
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeVectorOp_get_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeColorOp = GodotVisualShaderNodeColorOp GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeColorOp where
        type BaseClass GodotVisualShaderNodeColorOp = GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeColorOp_set_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeColorOp" $
        \ clsNamePtr ->
          withCString "set_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeColorOp_set_operator #-}

instance Method "set_operator" GodotVisualShaderNodeColorOp
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeColorOp_set_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeColorOp_get_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeColorOp" $
        \ clsNamePtr ->
          withCString "get_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeColorOp_get_operator #-}

instance Method "get_operator" GodotVisualShaderNodeColorOp
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeColorOp_get_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeTransformMult = GodotVisualShaderNodeTransformMult GodotObject
                                               deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTransformMult where
        type BaseClass GodotVisualShaderNodeTransformMult =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeTransformMult_set_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeTransformMult" $
        \ clsNamePtr ->
          withCString "set_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTransformMult_set_operator #-}

instance Method "set_operator" GodotVisualShaderNodeTransformMult
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTransformMult_set_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTransformMult_get_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeTransformMult" $
        \ clsNamePtr ->
          withCString "get_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTransformMult_get_operator #-}

instance Method "get_operator" GodotVisualShaderNodeTransformMult
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTransformMult_get_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeTransformVecMult = GodotVisualShaderNodeTransformVecMult GodotObject
                                                  deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTransformVecMult where
        type BaseClass GodotVisualShaderNodeTransformVecMult =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeTransformVecMult_set_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeTransformVecMult" $
        \ clsNamePtr ->
          withCString "set_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTransformVecMult_set_operator #-}

instance Method "set_operator"
           GodotVisualShaderNodeTransformVecMult
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTransformVecMult_set_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTransformVecMult_get_operator
  = unsafePerformIO $
      withCString "VisualShaderNodeTransformVecMult" $
        \ clsNamePtr ->
          withCString "get_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTransformVecMult_get_operator #-}

instance Method "get_operator"
           GodotVisualShaderNodeTransformVecMult
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTransformVecMult_get_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeScalarFunc = GodotVisualShaderNodeScalarFunc GodotObject
                                            deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeScalarFunc where
        type BaseClass GodotVisualShaderNodeScalarFunc =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeScalarFunc_set_function
  = unsafePerformIO $
      withCString "VisualShaderNodeScalarFunc" $
        \ clsNamePtr ->
          withCString "set_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeScalarFunc_set_function #-}

instance Method "set_function" GodotVisualShaderNodeScalarFunc
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeScalarFunc_set_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeScalarFunc_get_function
  = unsafePerformIO $
      withCString "VisualShaderNodeScalarFunc" $
        \ clsNamePtr ->
          withCString "get_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeScalarFunc_get_function #-}

instance Method "get_function" GodotVisualShaderNodeScalarFunc
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeScalarFunc_get_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeVectorFunc = GodotVisualShaderNodeVectorFunc GodotObject
                                            deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVectorFunc where
        type BaseClass GodotVisualShaderNodeVectorFunc =
             GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeVectorFunc_set_function
  = unsafePerformIO $
      withCString "VisualShaderNodeVectorFunc" $
        \ clsNamePtr ->
          withCString "set_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeVectorFunc_set_function #-}

instance Method "set_function" GodotVisualShaderNodeVectorFunc
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeVectorFunc_set_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeVectorFunc_get_function
  = unsafePerformIO $
      withCString "VisualShaderNodeVectorFunc" $
        \ clsNamePtr ->
          withCString "get_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeVectorFunc_get_function #-}

instance Method "get_function" GodotVisualShaderNodeVectorFunc
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeVectorFunc_get_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeDotProduct = GodotVisualShaderNodeDotProduct GodotObject
                                            deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeDotProduct where
        type BaseClass GodotVisualShaderNodeDotProduct =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeVectorLen = GodotVisualShaderNodeVectorLen GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVectorLen where
        type BaseClass GodotVisualShaderNodeVectorLen =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeScalarInterp = GodotVisualShaderNodeScalarInterp GodotObject
                                              deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeScalarInterp where
        type BaseClass GodotVisualShaderNodeScalarInterp =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeVectorInterp = GodotVisualShaderNodeVectorInterp GodotObject
                                              deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVectorInterp where
        type BaseClass GodotVisualShaderNodeVectorInterp =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeVectorCompose = GodotVisualShaderNodeVectorCompose GodotObject
                                               deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVectorCompose where
        type BaseClass GodotVisualShaderNodeVectorCompose =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeTransformCompose = GodotVisualShaderNodeTransformCompose GodotObject
                                                  deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTransformCompose where
        type BaseClass GodotVisualShaderNodeTransformCompose =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeVectorDecompose = GodotVisualShaderNodeVectorDecompose GodotObject
                                                 deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVectorDecompose where
        type BaseClass GodotVisualShaderNodeVectorDecompose =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeTransformDecompose = GodotVisualShaderNodeTransformDecompose GodotObject
                                                    deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTransformDecompose where
        type BaseClass GodotVisualShaderNodeTransformDecompose =
             GodotVisualShaderNode
        super = coerce

newtype GodotVisualShaderNodeTexture = GodotVisualShaderNodeTexture GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTexture where
        type BaseClass GodotVisualShaderNodeTexture = GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeTexture_set_source
  = unsafePerformIO $
      withCString "VisualShaderNodeTexture" $
        \ clsNamePtr ->
          withCString "set_source" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTexture_set_source #-}

instance Method "set_source" GodotVisualShaderNodeTexture
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeTexture_set_source
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTexture_get_source
  = unsafePerformIO $
      withCString "VisualShaderNodeTexture" $
        \ clsNamePtr ->
          withCString "get_source" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTexture_get_source #-}

instance Method "get_source" GodotVisualShaderNodeTexture (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeTexture_get_source
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTexture_set_texture
  = unsafePerformIO $
      withCString "VisualShaderNodeTexture" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTexture_set_texture #-}

instance Method "set_texture" GodotVisualShaderNodeTexture
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeTexture_set_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTexture_get_texture
  = unsafePerformIO $
      withCString "VisualShaderNodeTexture" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTexture_get_texture #-}

instance Method "get_texture" GodotVisualShaderNodeTexture
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeTexture_get_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTexture_set_texture_type
  = unsafePerformIO $
      withCString "VisualShaderNodeTexture" $
        \ clsNamePtr ->
          withCString "set_texture_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTexture_set_texture_type #-}

instance Method "set_texture_type" GodotVisualShaderNodeTexture
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeTexture_set_texture_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTexture_get_texture_type
  = unsafePerformIO $
      withCString "VisualShaderNodeTexture" $
        \ clsNamePtr ->
          withCString "get_texture_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTexture_get_texture_type #-}

instance Method "get_texture_type" GodotVisualShaderNodeTexture
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeTexture_get_texture_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeCubeMap = GodotVisualShaderNodeCubeMap GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeCubeMap where
        type BaseClass GodotVisualShaderNodeCubeMap = GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeCubeMap_set_cube_map
  = unsafePerformIO $
      withCString "VisualShaderNodeCubeMap" $
        \ clsNamePtr ->
          withCString "set_cube_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeCubeMap_set_cube_map #-}

instance Method "set_cube_map" GodotVisualShaderNodeCubeMap
           (GodotCubeMap -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeCubeMap_set_cube_map
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeCubeMap_get_cube_map
  = unsafePerformIO $
      withCString "VisualShaderNodeCubeMap" $
        \ clsNamePtr ->
          withCString "get_cube_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeCubeMap_get_cube_map #-}

instance Method "get_cube_map" GodotVisualShaderNodeCubeMap
           (IO GodotCubeMap)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeCubeMap_get_cube_map
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeCubeMap_set_texture_type
  = unsafePerformIO $
      withCString "VisualShaderNodeCubeMap" $
        \ clsNamePtr ->
          withCString "set_texture_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeCubeMap_set_texture_type #-}

instance Method "set_texture_type" GodotVisualShaderNodeCubeMap
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeCubeMap_set_texture_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeCubeMap_get_texture_type
  = unsafePerformIO $
      withCString "VisualShaderNodeCubeMap" $
        \ clsNamePtr ->
          withCString "get_texture_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeCubeMap_get_texture_type #-}

instance Method "get_texture_type" GodotVisualShaderNodeCubeMap
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeCubeMap_get_texture_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCubeMap = GodotCubeMap GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotCubeMap where
        type BaseClass GodotCubeMap = GodotResource
        super = coerce
bindCubeMap_get_width
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_get_width #-}

instance Method "get_width" GodotCubeMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_get_width (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_get_height
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_get_height #-}

instance Method "get_height" GodotCubeMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_get_height (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_set_flags
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "set_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_set_flags #-}

instance Method "set_flags" GodotCubeMap (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_set_flags (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_get_flags
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "get_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_get_flags #-}

instance Method "get_flags" GodotCubeMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_get_flags (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_set_side
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "set_side" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_set_side #-}

instance Method "set_side" GodotCubeMap
           (Int -> GodotImage -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_set_side (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_get_side
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "get_side" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_get_side #-}

instance Method "get_side" GodotCubeMap (Int -> IO GodotImage)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_get_side (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_set_storage
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "set_storage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_set_storage #-}

instance Method "set_storage" GodotCubeMap (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_set_storage (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_get_storage
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "get_storage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_get_storage #-}

instance Method "get_storage" GodotCubeMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_get_storage (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_set_lossy_storage_quality
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "set_lossy_storage_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_set_lossy_storage_quality #-}

instance Method "set_lossy_storage_quality" GodotCubeMap
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_set_lossy_storage_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMap_get_lossy_storage_quality
  = unsafePerformIO $
      withCString "CubeMap" $
        \ clsNamePtr ->
          withCString "get_lossy_storage_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMap_get_lossy_storage_quality #-}

instance Method "get_lossy_storage_quality" GodotCubeMap (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMap_get_lossy_storage_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeUniform = GodotVisualShaderNodeUniform GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeUniform where
        type BaseClass GodotVisualShaderNodeUniform = GodotVisualShaderNode
        super = coerce
bindVisualShaderNodeUniform_set_uniform_name
  = unsafePerformIO $
      withCString "VisualShaderNodeUniform" $
        \ clsNamePtr ->
          withCString "set_uniform_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeUniform_set_uniform_name #-}

instance Method "set_uniform_name" GodotVisualShaderNodeUniform
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeUniform_set_uniform_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeUniform_get_uniform_name
  = unsafePerformIO $
      withCString "VisualShaderNodeUniform" $
        \ clsNamePtr ->
          withCString "get_uniform_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeUniform_get_uniform_name #-}

instance Method "get_uniform_name" GodotVisualShaderNodeUniform
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualShaderNodeUniform_get_uniform_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeScalarUniform = GodotVisualShaderNodeScalarUniform GodotObject
                                               deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeScalarUniform where
        type BaseClass GodotVisualShaderNodeScalarUniform =
             GodotVisualShaderNodeUniform
        super = coerce

newtype GodotVisualShaderNodeColorUniform = GodotVisualShaderNodeColorUniform GodotObject
                                              deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeColorUniform where
        type BaseClass GodotVisualShaderNodeColorUniform =
             GodotVisualShaderNodeUniform
        super = coerce

newtype GodotVisualShaderNodeVec3Uniform = GodotVisualShaderNodeVec3Uniform GodotObject
                                             deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeVec3Uniform where
        type BaseClass GodotVisualShaderNodeVec3Uniform =
             GodotVisualShaderNodeUniform
        super = coerce

newtype GodotVisualShaderNodeTransformUniform = GodotVisualShaderNodeTransformUniform GodotObject
                                                  deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTransformUniform where
        type BaseClass GodotVisualShaderNodeTransformUniform =
             GodotVisualShaderNodeUniform
        super = coerce

newtype GodotVisualShaderNodeTextureUniform = GodotVisualShaderNodeTextureUniform GodotObject
                                                deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeTextureUniform where
        type BaseClass GodotVisualShaderNodeTextureUniform =
             GodotVisualShaderNodeUniform
        super = coerce
bindVisualShaderNodeTextureUniform_set_texture_type
  = unsafePerformIO $
      withCString "VisualShaderNodeTextureUniform" $
        \ clsNamePtr ->
          withCString "set_texture_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTextureUniform_set_texture_type
             #-}

instance Method "set_texture_type"
           GodotVisualShaderNodeTextureUniform
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTextureUniform_set_texture_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTextureUniform_get_texture_type
  = unsafePerformIO $
      withCString "VisualShaderNodeTextureUniform" $
        \ clsNamePtr ->
          withCString "get_texture_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTextureUniform_get_texture_type
             #-}

instance Method "get_texture_type"
           GodotVisualShaderNodeTextureUniform
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTextureUniform_get_texture_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTextureUniform_set_color_default
  = unsafePerformIO $
      withCString "VisualShaderNodeTextureUniform" $
        \ clsNamePtr ->
          withCString "set_color_default" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTextureUniform_set_color_default
             #-}

instance Method "set_color_default"
           GodotVisualShaderNodeTextureUniform
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTextureUniform_set_color_default
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualShaderNodeTextureUniform_get_color_default
  = unsafePerformIO $
      withCString "VisualShaderNodeTextureUniform" $
        \ clsNamePtr ->
          withCString "get_color_default" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualShaderNodeTextureUniform_get_color_default
             #-}

instance Method "get_color_default"
           GodotVisualShaderNodeTextureUniform
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualShaderNodeTextureUniform_get_color_default
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualShaderNodeCubeMapUniform = GodotVisualShaderNodeCubeMapUniform GodotObject
                                                deriving newtype AsVariant

instance HasBaseClass GodotVisualShaderNodeCubeMapUniform where
        type BaseClass GodotVisualShaderNodeCubeMapUniform =
             GodotVisualShaderNode
        super = coerce

newtype GodotMaterial = GodotMaterial GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotMaterial where
        type BaseClass GodotMaterial = GodotResource
        super = coerce
bindMaterial_set_next_pass
  = unsafePerformIO $
      withCString "Material" $
        \ clsNamePtr ->
          withCString "set_next_pass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMaterial_set_next_pass #-}

instance Method "set_next_pass" GodotMaterial
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMaterial_set_next_pass (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMaterial_get_next_pass
  = unsafePerformIO $
      withCString "Material" $
        \ clsNamePtr ->
          withCString "get_next_pass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMaterial_get_next_pass #-}

instance Method "get_next_pass" GodotMaterial (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMaterial_get_next_pass (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMaterial_set_render_priority
  = unsafePerformIO $
      withCString "Material" $
        \ clsNamePtr ->
          withCString "set_render_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMaterial_set_render_priority #-}

instance Method "set_render_priority" GodotMaterial (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMaterial_set_render_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMaterial_get_render_priority
  = unsafePerformIO $
      withCString "Material" $
        \ clsNamePtr ->
          withCString "get_render_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMaterial_get_render_priority #-}

instance Method "get_render_priority" GodotMaterial (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMaterial_get_render_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotShaderMaterial = GodotShaderMaterial GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotShaderMaterial where
        type BaseClass GodotShaderMaterial = GodotMaterial
        super = coerce
bindShaderMaterial_set_shader
  = unsafePerformIO $
      withCString "ShaderMaterial" $
        \ clsNamePtr ->
          withCString "set_shader" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShaderMaterial_set_shader #-}

instance Method "set_shader" GodotShaderMaterial
           (GodotShader -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShaderMaterial_set_shader (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShaderMaterial_get_shader
  = unsafePerformIO $
      withCString "ShaderMaterial" $
        \ clsNamePtr ->
          withCString "get_shader" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShaderMaterial_get_shader #-}

instance Method "get_shader" GodotShaderMaterial (IO GodotShader)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShaderMaterial_get_shader (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShaderMaterial_set_shader_param
  = unsafePerformIO $
      withCString "ShaderMaterial" $
        \ clsNamePtr ->
          withCString "set_shader_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShaderMaterial_set_shader_param #-}

instance Method "set_shader_param" GodotShaderMaterial
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShaderMaterial_set_shader_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShaderMaterial_get_shader_param
  = unsafePerformIO $
      withCString "ShaderMaterial" $
        \ clsNamePtr ->
          withCString "get_shader_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShaderMaterial_get_shader_param #-}

instance Method "get_shader_param" GodotShaderMaterial
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShaderMaterial_get_shader_param
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShaderMaterial__shader_changed
  = unsafePerformIO $
      withCString "ShaderMaterial" $
        \ clsNamePtr ->
          withCString "_shader_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShaderMaterial__shader_changed #-}

instance Method "_shader_changed" GodotShaderMaterial (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShaderMaterial__shader_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShaderMaterial_property_can_revert
  = unsafePerformIO $
      withCString "ShaderMaterial" $
        \ clsNamePtr ->
          withCString "property_can_revert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShaderMaterial_property_can_revert #-}

instance Method "property_can_revert" GodotShaderMaterial
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShaderMaterial_property_can_revert
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShaderMaterial_property_get_revert
  = unsafePerformIO $
      withCString "ShaderMaterial" $
        \ clsNamePtr ->
          withCString "property_get_revert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShaderMaterial_property_get_revert #-}

instance Method "property_get_revert" GodotShaderMaterial
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShaderMaterial_property_get_revert
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCanvasItemMaterial = GodotCanvasItemMaterial GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotCanvasItemMaterial where
        type BaseClass GodotCanvasItemMaterial = GodotMaterial
        super = coerce
bindCanvasItemMaterial_set_blend_mode
  = unsafePerformIO $
      withCString "CanvasItemMaterial" $
        \ clsNamePtr ->
          withCString "set_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItemMaterial_set_blend_mode #-}

instance Method "set_blend_mode" GodotCanvasItemMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItemMaterial_set_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItemMaterial_get_blend_mode
  = unsafePerformIO $
      withCString "CanvasItemMaterial" $
        \ clsNamePtr ->
          withCString "get_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItemMaterial_get_blend_mode #-}

instance Method "get_blend_mode" GodotCanvasItemMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItemMaterial_get_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItemMaterial_set_light_mode
  = unsafePerformIO $
      withCString "CanvasItemMaterial" $
        \ clsNamePtr ->
          withCString "set_light_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItemMaterial_set_light_mode #-}

instance Method "set_light_mode" GodotCanvasItemMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItemMaterial_set_light_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCanvasItemMaterial_get_light_mode
  = unsafePerformIO $
      withCString "CanvasItemMaterial" $
        \ clsNamePtr ->
          withCString "get_light_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCanvasItemMaterial_get_light_mode #-}

instance Method "get_light_mode" GodotCanvasItemMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCanvasItemMaterial_get_light_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCPUParticles2D = GodotCPUParticles2D GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotCPUParticles2D where
        type BaseClass GodotCPUParticles2D = GodotNode2D
        super = coerce
bindCPUParticles2D_set_emitting
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_emitting #-}

instance Method "set_emitting" GodotCPUParticles2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_amount
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_amount #-}

instance Method "set_amount" GodotCPUParticles2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_lifetime
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_lifetime #-}

instance Method "set_lifetime" GodotCPUParticles2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_one_shot
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_one_shot #-}

instance Method "set_one_shot" GodotCPUParticles2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_pre_process_time
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_pre_process_time #-}

instance Method "set_pre_process_time" GodotCPUParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_explosiveness_ratio
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_explosiveness_ratio #-}

instance Method "set_explosiveness_ratio" GodotCPUParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_randomness_ratio
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_randomness_ratio #-}

instance Method "set_randomness_ratio" GodotCPUParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_use_local_coordinates
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_use_local_coordinates #-}

instance Method "set_use_local_coordinates" GodotCPUParticles2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_fixed_fps
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_fixed_fps #-}

instance Method "set_fixed_fps" GodotCPUParticles2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_fixed_fps
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_fractional_delta
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_fractional_delta #-}

instance Method "set_fractional_delta" GodotCPUParticles2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_speed_scale
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_speed_scale #-}

instance Method "set_speed_scale" GodotCPUParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_is_emitting
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "is_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_is_emitting #-}

instance Method "is_emitting" GodotCPUParticles2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_is_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_amount
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_amount #-}

instance Method "get_amount" GodotCPUParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_lifetime
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_lifetime #-}

instance Method "get_lifetime" GodotCPUParticles2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_one_shot
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_one_shot #-}

instance Method "get_one_shot" GodotCPUParticles2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_pre_process_time
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_pre_process_time #-}

instance Method "get_pre_process_time" GodotCPUParticles2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_explosiveness_ratio
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_explosiveness_ratio #-}

instance Method "get_explosiveness_ratio" GodotCPUParticles2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_randomness_ratio
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_randomness_ratio #-}

instance Method "get_randomness_ratio" GodotCPUParticles2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_use_local_coordinates
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_use_local_coordinates #-}

instance Method "get_use_local_coordinates" GodotCPUParticles2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_fixed_fps
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_fixed_fps #-}

instance Method "get_fixed_fps" GodotCPUParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_fixed_fps
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_fractional_delta
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_fractional_delta #-}

instance Method "get_fractional_delta" GodotCPUParticles2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_speed_scale
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_speed_scale #-}

instance Method "get_speed_scale" GodotCPUParticles2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_draw_order
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_draw_order #-}

instance Method "set_draw_order" GodotCPUParticles2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_draw_order
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_draw_order
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_draw_order #-}

instance Method "get_draw_order" GodotCPUParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_draw_order
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_texture
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_texture #-}

instance Method "set_texture" GodotCPUParticles2D
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_texture
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_texture #-}

instance Method "get_texture" GodotCPUParticles2D (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_normalmap
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_normalmap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_normalmap #-}

instance Method "set_normalmap" GodotCPUParticles2D
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_normalmap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_normalmap
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_normalmap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_normalmap #-}

instance Method "get_normalmap" GodotCPUParticles2D
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_normalmap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_restart
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "restart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_restart #-}

instance Method "restart" GodotCPUParticles2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_restart (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_spread
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_spread #-}

instance Method "set_spread" GodotCPUParticles2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_spread (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_spread
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_spread #-}

instance Method "get_spread" GodotCPUParticles2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_spread (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_flatness
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_flatness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_flatness #-}

instance Method "set_flatness" GodotCPUParticles2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_flatness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_flatness
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_flatness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_flatness #-}

instance Method "get_flatness" GodotCPUParticles2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_flatness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_param
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_param #-}

instance Method "set_param" GodotCPUParticles2D
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_param
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_param #-}

instance Method "get_param" GodotCPUParticles2D (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_param_randomness
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_param_randomness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_param_randomness #-}

instance Method "set_param_randomness" GodotCPUParticles2D
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_param_randomness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_param_randomness
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_param_randomness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_param_randomness #-}

instance Method "get_param_randomness" GodotCPUParticles2D
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_param_randomness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_param_curve
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_param_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_param_curve #-}

instance Method "set_param_curve" GodotCPUParticles2D
           (Int -> GodotCurve -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_param_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_param_curve
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_param_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_param_curve #-}

instance Method "get_param_curve" GodotCPUParticles2D
           (Int -> IO GodotCurve)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_param_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_color
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_color #-}

instance Method "set_color" GodotCPUParticles2D
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_color
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_color #-}

instance Method "get_color" GodotCPUParticles2D (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_color_ramp
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_color_ramp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_color_ramp #-}

instance Method "set_color_ramp" GodotCPUParticles2D
           (GodotGradient -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_color_ramp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_color_ramp
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_color_ramp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_color_ramp #-}

instance Method "get_color_ramp" GodotCPUParticles2D
           (IO GodotGradient)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_color_ramp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_particle_flag
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_particle_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_particle_flag #-}

instance Method "set_particle_flag" GodotCPUParticles2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_particle_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_particle_flag
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_particle_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_particle_flag #-}

instance Method "get_particle_flag" GodotCPUParticles2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_particle_flag
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_emission_shape
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_emission_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_emission_shape #-}

instance Method "set_emission_shape" GodotCPUParticles2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_emission_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_emission_shape
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_emission_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_emission_shape #-}

instance Method "get_emission_shape" GodotCPUParticles2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_emission_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_emission_sphere_radius
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_emission_sphere_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_emission_sphere_radius #-}

instance Method "set_emission_sphere_radius" GodotCPUParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCPUParticles2D_set_emission_sphere_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_emission_sphere_radius
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_emission_sphere_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_emission_sphere_radius #-}

instance Method "get_emission_sphere_radius" GodotCPUParticles2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCPUParticles2D_get_emission_sphere_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_emission_rect_extents
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_emission_rect_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_emission_rect_extents #-}

instance Method "set_emission_rect_extents" GodotCPUParticles2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_emission_rect_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_emission_rect_extents
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_emission_rect_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_emission_rect_extents #-}

instance Method "get_emission_rect_extents" GodotCPUParticles2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_emission_rect_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_emission_points
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_emission_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_emission_points #-}

instance Method "set_emission_points" GodotCPUParticles2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_emission_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_emission_points
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_emission_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_emission_points #-}

instance Method "get_emission_points" GodotCPUParticles2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_emission_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_emission_normals
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_emission_normals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_emission_normals #-}

instance Method "set_emission_normals" GodotCPUParticles2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_emission_normals
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_emission_normals
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_emission_normals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_emission_normals #-}

instance Method "get_emission_normals" GodotCPUParticles2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_emission_normals
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_emission_colors
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_emission_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_emission_colors #-}

instance Method "set_emission_colors" GodotCPUParticles2D
           (GodotPoolColorArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_emission_colors
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_emission_colors
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_emission_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_emission_colors #-}

instance Method "get_emission_colors" GodotCPUParticles2D
           (IO GodotPoolColorArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_emission_colors
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_get_gravity
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "get_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_get_gravity #-}

instance Method "get_gravity" GodotCPUParticles2D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_get_gravity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_set_gravity
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "set_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_set_gravity #-}

instance Method "set_gravity" GodotCPUParticles2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_set_gravity (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D_convert_from_particles
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "convert_from_particles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D_convert_from_particles #-}

instance Method "convert_from_particles" GodotCPUParticles2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D_convert_from_particles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCPUParticles2D__update_render_thread
  = unsafePerformIO $
      withCString "CPUParticles2D" $
        \ clsNamePtr ->
          withCString "_update_render_thread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCPUParticles2D__update_render_thread #-}

instance Method "_update_render_thread" GodotCPUParticles2D (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCPUParticles2D__update_render_thread
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotParticles2D = GodotParticles2D GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotParticles2D where
        type BaseClass GodotParticles2D = GodotNode2D
        super = coerce
bindParticles2D_set_emitting
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_emitting #-}

instance Method "set_emitting" GodotParticles2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_amount
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_amount #-}

instance Method "set_amount" GodotParticles2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_lifetime
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_lifetime #-}

instance Method "set_lifetime" GodotParticles2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_one_shot
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_one_shot #-}

instance Method "set_one_shot" GodotParticles2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_pre_process_time
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_pre_process_time #-}

instance Method "set_pre_process_time" GodotParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_explosiveness_ratio
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_explosiveness_ratio #-}

instance Method "set_explosiveness_ratio" GodotParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_randomness_ratio
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_randomness_ratio #-}

instance Method "set_randomness_ratio" GodotParticles2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_visibility_rect
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_visibility_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_visibility_rect #-}

instance Method "set_visibility_rect" GodotParticles2D
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_visibility_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_use_local_coordinates
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_use_local_coordinates #-}

instance Method "set_use_local_coordinates" GodotParticles2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_fixed_fps
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_fixed_fps #-}

instance Method "set_fixed_fps" GodotParticles2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_fixed_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_fractional_delta
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_fractional_delta #-}

instance Method "set_fractional_delta" GodotParticles2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_process_material
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_process_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_process_material #-}

instance Method "set_process_material" GodotParticles2D
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_process_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_speed_scale
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_speed_scale #-}

instance Method "set_speed_scale" GodotParticles2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_speed_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_is_emitting
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "is_emitting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_is_emitting #-}

instance Method "is_emitting" GodotParticles2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_is_emitting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_amount
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_amount" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_amount #-}

instance Method "get_amount" GodotParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_amount (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_lifetime
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_lifetime" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_lifetime #-}

instance Method "get_lifetime" GodotParticles2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_lifetime (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_one_shot
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_one_shot" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_one_shot #-}

instance Method "get_one_shot" GodotParticles2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_one_shot (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_pre_process_time
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_pre_process_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_pre_process_time #-}

instance Method "get_pre_process_time" GodotParticles2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_pre_process_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_explosiveness_ratio
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_explosiveness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_explosiveness_ratio #-}

instance Method "get_explosiveness_ratio" GodotParticles2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_explosiveness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_randomness_ratio
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_randomness_ratio" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_randomness_ratio #-}

instance Method "get_randomness_ratio" GodotParticles2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_randomness_ratio
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_visibility_rect
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_visibility_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_visibility_rect #-}

instance Method "get_visibility_rect" GodotParticles2D
           (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_visibility_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_use_local_coordinates
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_use_local_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_use_local_coordinates #-}

instance Method "get_use_local_coordinates" GodotParticles2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_use_local_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_fixed_fps
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_fixed_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_fixed_fps #-}

instance Method "get_fixed_fps" GodotParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_fixed_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_fractional_delta
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_fractional_delta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_fractional_delta #-}

instance Method "get_fractional_delta" GodotParticles2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_fractional_delta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_process_material
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_process_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_process_material #-}

instance Method "get_process_material" GodotParticles2D
           (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_process_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_speed_scale
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_speed_scale #-}

instance Method "get_speed_scale" GodotParticles2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_speed_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_draw_order
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_draw_order #-}

instance Method "set_draw_order" GodotParticles2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_draw_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_draw_order
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_draw_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_draw_order #-}

instance Method "get_draw_order" GodotParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_draw_order (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_texture
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_texture #-}

instance Method "set_texture" GodotParticles2D
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_texture
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_texture #-}

instance Method "get_texture" GodotParticles2D (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_normal_map
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_normal_map #-}

instance Method "set_normal_map" GodotParticles2D
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_normal_map (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_normal_map
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_normal_map #-}

instance Method "get_normal_map" GodotParticles2D (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_normal_map (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_capture_rect
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "capture_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_capture_rect #-}

instance Method "capture_rect" GodotParticles2D (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_capture_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_v_frames
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_v_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_v_frames #-}

instance Method "set_v_frames" GodotParticles2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_v_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_v_frames
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_v_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_v_frames #-}

instance Method "get_v_frames" GodotParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_v_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_set_h_frames
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "set_h_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_set_h_frames #-}

instance Method "set_h_frames" GodotParticles2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_set_h_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_get_h_frames
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "get_h_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_get_h_frames #-}

instance Method "get_h_frames" GodotParticles2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_get_h_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticles2D_restart
  = unsafePerformIO $
      withCString "Particles2D" $
        \ clsNamePtr ->
          withCString "restart" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticles2D_restart #-}

instance Method "restart" GodotParticles2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticles2D_restart (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSprite = GodotSprite GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotSprite where
        type BaseClass GodotSprite = GodotNode2D
        super = coerce
bindSprite_set_texture
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_texture #-}

instance Method "set_texture" GodotSprite (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_texture
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_texture #-}

instance Method "get_texture" GodotSprite (IO GodotTexture) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_normal_map
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_normal_map #-}

instance Method "set_normal_map" GodotSprite
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_normal_map (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_normal_map
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_normal_map #-}

instance Method "get_normal_map" GodotSprite (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_normal_map (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_centered
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_centered #-}

instance Method "set_centered" GodotSprite (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_centered (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_is_centered
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "is_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_is_centered #-}

instance Method "is_centered" GodotSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_is_centered (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_offset
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_offset #-}

instance Method "set_offset" GodotSprite (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_offset
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_offset #-}

instance Method "get_offset" GodotSprite (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_flip_h
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_flip_h" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_flip_h #-}

instance Method "set_flip_h" GodotSprite (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_flip_h (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_is_flipped_h
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "is_flipped_h" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_is_flipped_h #-}

instance Method "is_flipped_h" GodotSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_is_flipped_h (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_flip_v
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_flip_v" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_flip_v #-}

instance Method "set_flip_v" GodotSprite (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_flip_v (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_is_flipped_v
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "is_flipped_v" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_is_flipped_v #-}

instance Method "is_flipped_v" GodotSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_is_flipped_v (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_region
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_region #-}

instance Method "set_region" GodotSprite (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_region (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_is_region
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "is_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_is_region #-}

instance Method "is_region" GodotSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_is_region (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_is_pixel_opaque
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "is_pixel_opaque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_is_pixel_opaque #-}

instance Method "is_pixel_opaque" GodotSprite
           (GodotVector2 -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_is_pixel_opaque (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_region_rect
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_region_rect #-}

instance Method "set_region_rect" GodotSprite (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_region_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_region_rect
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_region_rect #-}

instance Method "get_region_rect" GodotSprite (IO GodotRect2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_region_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_region_filter_clip
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_region_filter_clip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_region_filter_clip #-}

instance Method "set_region_filter_clip" GodotSprite
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_region_filter_clip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_is_region_filter_clip_enabled
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "is_region_filter_clip_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_is_region_filter_clip_enabled #-}

instance Method "is_region_filter_clip_enabled" GodotSprite
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_is_region_filter_clip_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_frame
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_frame #-}

instance Method "set_frame" GodotSprite (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_frame (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_frame
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_frame #-}

instance Method "get_frame" GodotSprite (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_frame (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_vframes
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_vframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_vframes #-}

instance Method "set_vframes" GodotSprite (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_vframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_vframes
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_vframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_vframes #-}

instance Method "get_vframes" GodotSprite (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_vframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_set_hframes
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "set_hframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_set_hframes #-}

instance Method "set_hframes" GodotSprite (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_set_hframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_hframes
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_hframes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_hframes #-}

instance Method "get_hframes" GodotSprite (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_hframes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSprite_get_rect
  = unsafePerformIO $
      withCString "Sprite" $
        \ clsNamePtr ->
          withCString "get_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSprite_get_rect #-}

instance Method "get_rect" GodotSprite (IO GodotRect2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSprite_get_rect (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimatedSprite = GodotAnimatedSprite GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotAnimatedSprite where
        type BaseClass GodotAnimatedSprite = GodotNode2D
        super = coerce
bindAnimatedSprite_set_sprite_frames
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_sprite_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_sprite_frames #-}

instance Method "set_sprite_frames" GodotAnimatedSprite
           (GodotSpriteFrames -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_sprite_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_get_sprite_frames
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "get_sprite_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_get_sprite_frames #-}

instance Method "get_sprite_frames" GodotAnimatedSprite
           (IO GodotSpriteFrames)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_get_sprite_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_set_animation
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_animation #-}

instance Method "set_animation" GodotAnimatedSprite
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_get_animation
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "get_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_get_animation #-}

instance Method "get_animation" GodotAnimatedSprite
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_get_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite__set_playing
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "_set_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite__set_playing #-}

instance Method "_set_playing" GodotAnimatedSprite (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite__set_playing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite__is_playing
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "_is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite__is_playing #-}

instance Method "_is_playing" GodotAnimatedSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite__is_playing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_play
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_play #-}

instance Method "play" GodotAnimatedSprite (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_play (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_stop
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_stop #-}

instance Method "stop" GodotAnimatedSprite (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_stop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_is_playing
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_is_playing #-}

instance Method "is_playing" GodotAnimatedSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_is_playing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_set_centered
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_centered #-}

instance Method "set_centered" GodotAnimatedSprite (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_centered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_is_centered
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "is_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_is_centered #-}

instance Method "is_centered" GodotAnimatedSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_is_centered (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_set_offset
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_offset #-}

instance Method "set_offset" GodotAnimatedSprite
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_get_offset
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_get_offset #-}

instance Method "get_offset" GodotAnimatedSprite (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_get_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_set_flip_h
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_flip_h" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_flip_h #-}

instance Method "set_flip_h" GodotAnimatedSprite (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_flip_h (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_is_flipped_h
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "is_flipped_h" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_is_flipped_h #-}

instance Method "is_flipped_h" GodotAnimatedSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_is_flipped_h (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_set_flip_v
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_flip_v" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_flip_v #-}

instance Method "set_flip_v" GodotAnimatedSprite (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_flip_v (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_is_flipped_v
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "is_flipped_v" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_is_flipped_v #-}

instance Method "is_flipped_v" GodotAnimatedSprite (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_is_flipped_v (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_set_frame
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_frame #-}

instance Method "set_frame" GodotAnimatedSprite (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_get_frame
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "get_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_get_frame #-}

instance Method "get_frame" GodotAnimatedSprite (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_get_frame (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_set_speed_scale
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "set_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_set_speed_scale #-}

instance Method "set_speed_scale" GodotAnimatedSprite
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_set_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite_get_speed_scale
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "get_speed_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite_get_speed_scale #-}

instance Method "get_speed_scale" GodotAnimatedSprite (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite_get_speed_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedSprite__res_changed
  = unsafePerformIO $
      withCString "AnimatedSprite" $
        \ clsNamePtr ->
          withCString "_res_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedSprite__res_changed #-}

instance Method "_res_changed" GodotAnimatedSprite (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedSprite__res_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPosition2D = GodotPosition2D GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotPosition2D where
        type BaseClass GodotPosition2D = GodotNode2D
        super = coerce

newtype GodotLine2D = GodotLine2D GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotLine2D where
        type BaseClass GodotLine2D = GodotNode2D
        super = coerce
bindLine2D_set_points
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_points #-}

instance Method "set_points" GodotLine2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_points (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_points
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_points #-}

instance Method "get_points" GodotLine2D (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_points (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_point_position
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_point_position #-}

instance Method "set_point_position" GodotLine2D
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_point_position
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_point_position #-}

instance Method "get_point_position" GodotLine2D
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_point_count
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_point_count #-}

instance Method "get_point_count" GodotLine2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_point_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_add_point
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "add_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_add_point #-}

instance Method "add_point" GodotLine2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_add_point (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_remove_point
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "remove_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_remove_point #-}

instance Method "remove_point" GodotLine2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_remove_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_width
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_width #-}

instance Method "set_width" GodotLine2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_width (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_width
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_width #-}

instance Method "get_width" GodotLine2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_width (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_default_color
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_default_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_default_color #-}

instance Method "set_default_color" GodotLine2D
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_default_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_default_color
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_default_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_default_color #-}

instance Method "get_default_color" GodotLine2D (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_default_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_gradient
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_gradient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_gradient #-}

instance Method "set_gradient" GodotLine2D (GodotGradient -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_gradient (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_gradient
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_gradient" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_gradient #-}

instance Method "get_gradient" GodotLine2D (IO GodotGradient) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_gradient (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_texture
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_texture #-}

instance Method "set_texture" GodotLine2D (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_texture
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_texture #-}

instance Method "get_texture" GodotLine2D (IO GodotTexture) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_texture_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_texture_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_texture_mode #-}

instance Method "set_texture_mode" GodotLine2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_texture_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_texture_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_texture_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_texture_mode #-}

instance Method "get_texture_mode" GodotLine2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_texture_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_joint_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_joint_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_joint_mode #-}

instance Method "set_joint_mode" GodotLine2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_joint_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_joint_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_joint_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_joint_mode #-}

instance Method "get_joint_mode" GodotLine2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_joint_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_begin_cap_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_begin_cap_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_begin_cap_mode #-}

instance Method "set_begin_cap_mode" GodotLine2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_begin_cap_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_begin_cap_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_begin_cap_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_begin_cap_mode #-}

instance Method "get_begin_cap_mode" GodotLine2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_begin_cap_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_end_cap_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_end_cap_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_end_cap_mode #-}

instance Method "set_end_cap_mode" GodotLine2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_end_cap_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_end_cap_mode
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_end_cap_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_end_cap_mode #-}

instance Method "get_end_cap_mode" GodotLine2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_end_cap_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_sharp_limit
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_sharp_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_sharp_limit #-}

instance Method "set_sharp_limit" GodotLine2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_sharp_limit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_sharp_limit
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_sharp_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_sharp_limit #-}

instance Method "get_sharp_limit" GodotLine2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_sharp_limit (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_set_round_precision
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "set_round_precision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_set_round_precision #-}

instance Method "set_round_precision" GodotLine2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_set_round_precision (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D_get_round_precision
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "get_round_precision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D_get_round_precision #-}

instance Method "get_round_precision" GodotLine2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D_get_round_precision (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLine2D__gradient_changed
  = unsafePerformIO $
      withCString "Line2D" $
        \ clsNamePtr ->
          withCString "_gradient_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLine2D__gradient_changed #-}

instance Method "_gradient_changed" GodotLine2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLine2D__gradient_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGradient = GodotGradient GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotGradient where
        type BaseClass GodotGradient = GodotResource
        super = coerce
bindGradient_add_point
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "add_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_add_point #-}

instance Method "add_point" GodotGradient
           (Float -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_add_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_remove_point
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "remove_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_remove_point #-}

instance Method "remove_point" GodotGradient (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_remove_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_set_offset
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_set_offset #-}

instance Method "set_offset" GodotGradient (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_set_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_get_offset
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_get_offset #-}

instance Method "get_offset" GodotGradient (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_get_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_set_color
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_set_color #-}

instance Method "set_color" GodotGradient
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_set_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_get_color
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_get_color #-}

instance Method "get_color" GodotGradient (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_get_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_interpolate
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "interpolate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_interpolate #-}

instance Method "interpolate" GodotGradient
           (Float -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_interpolate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_get_point_count
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "get_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_get_point_count #-}

instance Method "get_point_count" GodotGradient (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_get_point_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_set_offsets
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "set_offsets" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_set_offsets #-}

instance Method "set_offsets" GodotGradient
           (GodotPoolRealArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_set_offsets (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_get_offsets
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "get_offsets" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_get_offsets #-}

instance Method "get_offsets" GodotGradient (IO GodotPoolRealArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_get_offsets (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_set_colors
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "set_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_set_colors #-}

instance Method "set_colors" GodotGradient
           (GodotPoolColorArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_set_colors (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGradient_get_colors
  = unsafePerformIO $
      withCString "Gradient" $
        \ clsNamePtr ->
          withCString "get_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGradient_get_colors #-}

instance Method "get_colors" GodotGradient (IO GodotPoolColorArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGradient_get_colors (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMeshInstance2D = GodotMeshInstance2D GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotMeshInstance2D where
        type BaseClass GodotMeshInstance2D = GodotNode2D
        super = coerce
bindMeshInstance2D_set_mesh
  = unsafePerformIO $
      withCString "MeshInstance2D" $
        \ clsNamePtr ->
          withCString "set_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance2D_set_mesh #-}

instance Method "set_mesh" GodotMeshInstance2D (GodotMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance2D_set_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance2D_get_mesh
  = unsafePerformIO $
      withCString "MeshInstance2D" $
        \ clsNamePtr ->
          withCString "get_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance2D_get_mesh #-}

instance Method "get_mesh" GodotMeshInstance2D (IO GodotMesh) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance2D_get_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance2D_set_texture
  = unsafePerformIO $
      withCString "MeshInstance2D" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance2D_set_texture #-}

instance Method "set_texture" GodotMeshInstance2D
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance2D_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance2D_get_texture
  = unsafePerformIO $
      withCString "MeshInstance2D" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance2D_get_texture #-}

instance Method "get_texture" GodotMeshInstance2D (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance2D_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance2D_set_normal_map
  = unsafePerformIO $
      withCString "MeshInstance2D" $
        \ clsNamePtr ->
          withCString "set_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance2D_set_normal_map #-}

instance Method "set_normal_map" GodotMeshInstance2D
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance2D_set_normal_map
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshInstance2D_get_normal_map
  = unsafePerformIO $
      withCString "MeshInstance2D" $
        \ clsNamePtr ->
          withCString "get_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshInstance2D_get_normal_map #-}

instance Method "get_normal_map" GodotMeshInstance2D
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshInstance2D_get_normal_map
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCollisionObject2D = GodotCollisionObject2D GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotCollisionObject2D where
        type BaseClass GodotCollisionObject2D = GodotNode2D
        super = coerce
bindCollisionObject2D__input_event
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "_input_event" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D__input_event #-}

instance Method "_input_event" GodotCollisionObject2D
           (GodotObject -> GodotInputEvent -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D__input_event
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_get_rid
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "get_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_get_rid #-}

instance Method "get_rid" GodotCollisionObject2D (IO GodotRid)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_get_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_set_pickable
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "set_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_set_pickable #-}

instance Method "set_pickable" GodotCollisionObject2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_set_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_is_pickable
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "is_pickable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_is_pickable #-}

instance Method "is_pickable" GodotCollisionObject2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_is_pickable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_create_shape_owner
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "create_shape_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_create_shape_owner #-}

instance Method "create_shape_owner" GodotCollisionObject2D
           (GodotObject -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_create_shape_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_remove_shape_owner
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "remove_shape_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_remove_shape_owner #-}

instance Method "remove_shape_owner" GodotCollisionObject2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_remove_shape_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_get_shape_owners
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "get_shape_owners" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_get_shape_owners #-}

instance Method "get_shape_owners" GodotCollisionObject2D
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_get_shape_owners
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_set_transform
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_set_transform #-}

instance Method "shape_owner_set_transform" GodotCollisionObject2D
           (Int -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_get_transform
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_get_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_get_transform #-}

instance Method "shape_owner_get_transform" GodotCollisionObject2D
           (Int -> IO GodotTransform2d)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_get_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_get_owner
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_get_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_get_owner #-}

instance Method "shape_owner_get_owner" GodotCollisionObject2D
           (Int -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_shape_owner_get_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_set_disabled
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_set_disabled #-}

instance Method "shape_owner_set_disabled" GodotCollisionObject2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_set_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_is_shape_owner_disabled
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "is_shape_owner_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_is_shape_owner_disabled #-}

instance Method "is_shape_owner_disabled" GodotCollisionObject2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_is_shape_owner_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_set_one_way_collision
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_set_one_way_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_set_one_way_collision
             #-}

instance Method "shape_owner_set_one_way_collision"
           GodotCollisionObject2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_set_one_way_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_is_shape_owner_one_way_collision_enabled
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "is_shape_owner_one_way_collision_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_is_shape_owner_one_way_collision_enabled
             #-}

instance Method "is_shape_owner_one_way_collision_enabled"
           GodotCollisionObject2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_is_shape_owner_one_way_collision_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_add_shape
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_add_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_add_shape #-}

instance Method "shape_owner_add_shape" GodotCollisionObject2D
           (Int -> GodotShape2D -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_shape_owner_add_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_get_shape_count
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_get_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_get_shape_count #-}

instance Method "shape_owner_get_shape_count"
           GodotCollisionObject2D
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_get_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_get_shape
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_get_shape #-}

instance Method "shape_owner_get_shape" GodotCollisionObject2D
           (Int -> Int -> IO GodotShape2D)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_shape_owner_get_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_get_shape_index
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_get_shape_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_get_shape_index #-}

instance Method "shape_owner_get_shape_index"
           GodotCollisionObject2D
           (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_get_shape_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_remove_shape
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_remove_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_remove_shape #-}

instance Method "shape_owner_remove_shape" GodotCollisionObject2D
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_remove_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_owner_clear_shapes
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_owner_clear_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_owner_clear_shapes #-}

instance Method "shape_owner_clear_shapes" GodotCollisionObject2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionObject2D_shape_owner_clear_shapes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionObject2D_shape_find_owner
  = unsafePerformIO $
      withCString "CollisionObject2D" $
        \ clsNamePtr ->
          withCString "shape_find_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionObject2D_shape_find_owner #-}

instance Method "shape_find_owner" GodotCollisionObject2D
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionObject2D_shape_find_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPhysicsBody2D = GodotPhysicsBody2D GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotPhysicsBody2D where
        type BaseClass GodotPhysicsBody2D = GodotCollisionObject2D
        super = coerce
bindPhysicsBody2D_set_collision_layer
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_set_collision_layer #-}

instance Method "set_collision_layer" GodotPhysicsBody2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_set_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_get_collision_layer
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_get_collision_layer #-}

instance Method "get_collision_layer" GodotPhysicsBody2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_get_collision_layer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_set_collision_mask
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_set_collision_mask #-}

instance Method "set_collision_mask" GodotPhysicsBody2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_get_collision_mask
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_get_collision_mask #-}

instance Method "get_collision_mask" GodotPhysicsBody2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_set_collision_mask_bit
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotPhysicsBody2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_get_collision_mask_bit
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotPhysicsBody2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_set_collision_layer_bit
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "set_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_set_collision_layer_bit #-}

instance Method "set_collision_layer_bit" GodotPhysicsBody2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_set_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_get_collision_layer_bit
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "get_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_get_collision_layer_bit #-}

instance Method "get_collision_layer_bit" GodotPhysicsBody2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_get_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D__set_layers
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "_set_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D__set_layers #-}

instance Method "_set_layers" GodotPhysicsBody2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D__set_layers (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D__get_layers
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "_get_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D__get_layers #-}

instance Method "_get_layers" GodotPhysicsBody2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D__get_layers (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_get_collision_exceptions
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "get_collision_exceptions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_get_collision_exceptions #-}

instance Method "get_collision_exceptions" GodotPhysicsBody2D
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPhysicsBody2D_get_collision_exceptions
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_add_collision_exception_with
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "add_collision_exception_with" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_add_collision_exception_with #-}

instance Method "add_collision_exception_with" GodotPhysicsBody2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsBody2D_add_collision_exception_with
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPhysicsBody2D_remove_collision_exception_with
  = unsafePerformIO $
      withCString "PhysicsBody2D" $
        \ clsNamePtr ->
          withCString "remove_collision_exception_with" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPhysicsBody2D_remove_collision_exception_with #-}

instance Method "remove_collision_exception_with"
           GodotPhysicsBody2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindPhysicsBody2D_remove_collision_exception_with
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStaticBody2D = GodotStaticBody2D GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotStaticBody2D where
        type BaseClass GodotStaticBody2D = GodotPhysicsBody2D
        super = coerce
bindStaticBody2D_set_constant_linear_velocity
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "set_constant_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_set_constant_linear_velocity #-}

instance Method "set_constant_linear_velocity" GodotStaticBody2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody2D_set_constant_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_set_constant_angular_velocity
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "set_constant_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_set_constant_angular_velocity #-}

instance Method "set_constant_angular_velocity" GodotStaticBody2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody2D_set_constant_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_get_constant_linear_velocity
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "get_constant_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_get_constant_linear_velocity #-}

instance Method "get_constant_linear_velocity" GodotStaticBody2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody2D_get_constant_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_get_constant_angular_velocity
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "get_constant_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_get_constant_angular_velocity #-}

instance Method "get_constant_angular_velocity" GodotStaticBody2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody2D_get_constant_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_set_friction
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "set_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_set_friction #-}

instance Method "set_friction" GodotStaticBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody2D_set_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_get_friction
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "get_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_get_friction #-}

instance Method "get_friction" GodotStaticBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody2D_get_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_set_bounce
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "set_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_set_bounce #-}

instance Method "set_bounce" GodotStaticBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody2D_set_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_get_bounce
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "get_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_get_bounce #-}

instance Method "get_bounce" GodotStaticBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStaticBody2D_get_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_set_physics_material_override
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "set_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_set_physics_material_override #-}

instance Method "set_physics_material_override" GodotStaticBody2D
           (GodotPhysicsMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody2D_set_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D_get_physics_material_override
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "get_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D_get_physics_material_override #-}

instance Method "get_physics_material_override" GodotStaticBody2D
           (IO GodotPhysicsMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody2D_get_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStaticBody2D__reload_physics_characteristics
  = unsafePerformIO $
      withCString "StaticBody2D" $
        \ clsNamePtr ->
          withCString "_reload_physics_characteristics" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStaticBody2D__reload_physics_characteristics #-}

instance Method "_reload_physics_characteristics" GodotStaticBody2D
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStaticBody2D__reload_physics_characteristics
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRigidBody2D = GodotRigidBody2D GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotRigidBody2D where
        type BaseClass GodotRigidBody2D = GodotPhysicsBody2D
        super = coerce
bindRigidBody2D__integrate_forces
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "_integrate_forces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D__integrate_forces #-}

instance Method "_integrate_forces" GodotRigidBody2D
           (GodotPhysics2DDirectBodyState -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D__integrate_forces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_mode
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_mode #-}

instance Method "set_mode" GodotRigidBody2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_mode
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_mode #-}

instance Method "get_mode" GodotRigidBody2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_mass
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_mass #-}

instance Method "set_mass" GodotRigidBody2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_mass (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_mass
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_mass" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_mass #-}

instance Method "get_mass" GodotRigidBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_mass (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_inertia
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_inertia" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_inertia #-}

instance Method "get_inertia" GodotRigidBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_inertia (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_inertia
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_inertia" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_inertia #-}

instance Method "set_inertia" GodotRigidBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_inertia (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_weight
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_weight" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_weight #-}

instance Method "set_weight" GodotRigidBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_weight (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_weight
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_weight" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_weight #-}

instance Method "get_weight" GodotRigidBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_weight (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_friction
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_friction #-}

instance Method "set_friction" GodotRigidBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_friction
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_friction #-}

instance Method "get_friction" GodotRigidBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_friction (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_bounce
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_bounce #-}

instance Method "set_bounce" GodotRigidBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_bounce
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_bounce #-}

instance Method "get_bounce" GodotRigidBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_bounce (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_physics_material_override
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_physics_material_override #-}

instance Method "set_physics_material_override" GodotRigidBody2D
           (GodotPhysicsMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody2D_set_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_physics_material_override
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_physics_material_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_physics_material_override #-}

instance Method "get_physics_material_override" GodotRigidBody2D
           (IO GodotPhysicsMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody2D_get_physics_material_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D__reload_physics_characteristics
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "_reload_physics_characteristics" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D__reload_physics_characteristics #-}

instance Method "_reload_physics_characteristics" GodotRigidBody2D
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody2D__reload_physics_characteristics
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_gravity_scale
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_gravity_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_gravity_scale #-}

instance Method "set_gravity_scale" GodotRigidBody2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_gravity_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_gravity_scale
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_gravity_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_gravity_scale #-}

instance Method "get_gravity_scale" GodotRigidBody2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_gravity_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_linear_damp
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_linear_damp #-}

instance Method "set_linear_damp" GodotRigidBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_linear_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_linear_damp
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_linear_damp #-}

instance Method "get_linear_damp" GodotRigidBody2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_linear_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_angular_damp
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_angular_damp #-}

instance Method "set_angular_damp" GodotRigidBody2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_angular_damp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_angular_damp
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_angular_damp #-}

instance Method "get_angular_damp" GodotRigidBody2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_angular_damp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_linear_velocity
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_linear_velocity #-}

instance Method "set_linear_velocity" GodotRigidBody2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_linear_velocity
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_linear_velocity #-}

instance Method "get_linear_velocity" GodotRigidBody2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_angular_velocity
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_angular_velocity #-}

instance Method "set_angular_velocity" GodotRigidBody2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_angular_velocity
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_angular_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_angular_velocity #-}

instance Method "get_angular_velocity" GodotRigidBody2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_angular_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_max_contacts_reported
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_max_contacts_reported #-}

instance Method "set_max_contacts_reported" GodotRigidBody2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_max_contacts_reported
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_max_contacts_reported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_max_contacts_reported #-}

instance Method "get_max_contacts_reported" GodotRigidBody2D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_max_contacts_reported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_use_custom_integrator
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_use_custom_integrator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_use_custom_integrator #-}

instance Method "set_use_custom_integrator" GodotRigidBody2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_use_custom_integrator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_is_using_custom_integrator
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "is_using_custom_integrator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_is_using_custom_integrator #-}

instance Method "is_using_custom_integrator" GodotRigidBody2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_is_using_custom_integrator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_contact_monitor
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_contact_monitor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_contact_monitor #-}

instance Method "set_contact_monitor" GodotRigidBody2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_contact_monitor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_is_contact_monitor_enabled
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "is_contact_monitor_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_is_contact_monitor_enabled #-}

instance Method "is_contact_monitor_enabled" GodotRigidBody2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_is_contact_monitor_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_continuous_collision_detection_mode
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_continuous_collision_detection_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_continuous_collision_detection_mode
             #-}

instance Method "set_continuous_collision_detection_mode"
           GodotRigidBody2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody2D_set_continuous_collision_detection_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_continuous_collision_detection_mode
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_continuous_collision_detection_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_continuous_collision_detection_mode
             #-}

instance Method "get_continuous_collision_detection_mode"
           GodotRigidBody2D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRigidBody2D_get_continuous_collision_detection_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_axis_velocity
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_axis_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_axis_velocity #-}

instance Method "set_axis_velocity" GodotRigidBody2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_axis_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_apply_central_impulse
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "apply_central_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_apply_central_impulse #-}

instance Method "apply_central_impulse" GodotRigidBody2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_apply_central_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_apply_impulse
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "apply_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_apply_impulse #-}

instance Method "apply_impulse" GodotRigidBody2D
           (GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_apply_impulse (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_apply_torque_impulse
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "apply_torque_impulse" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_apply_torque_impulse #-}

instance Method "apply_torque_impulse" GodotRigidBody2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_apply_torque_impulse
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_applied_force
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_applied_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_applied_force #-}

instance Method "set_applied_force" GodotRigidBody2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_applied_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_applied_force
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_applied_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_applied_force #-}

instance Method "get_applied_force" GodotRigidBody2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_applied_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_applied_torque
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_applied_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_applied_torque #-}

instance Method "set_applied_torque" GodotRigidBody2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_applied_torque
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_applied_torque
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_applied_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_applied_torque #-}

instance Method "get_applied_torque" GodotRigidBody2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_applied_torque
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_add_central_force
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "add_central_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_add_central_force #-}

instance Method "add_central_force" GodotRigidBody2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_add_central_force
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_add_force
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "add_force" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_add_force #-}

instance Method "add_force" GodotRigidBody2D
           (GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_add_force (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_add_torque
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "add_torque" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_add_torque #-}

instance Method "add_torque" GodotRigidBody2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_add_torque (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_sleeping
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_sleeping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_sleeping #-}

instance Method "set_sleeping" GodotRigidBody2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_sleeping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_is_sleeping
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "is_sleeping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_is_sleeping #-}

instance Method "is_sleeping" GodotRigidBody2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_is_sleeping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_set_can_sleep
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "set_can_sleep" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_set_can_sleep #-}

instance Method "set_can_sleep" GodotRigidBody2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_set_can_sleep (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_is_able_to_sleep
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "is_able_to_sleep" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_is_able_to_sleep #-}

instance Method "is_able_to_sleep" GodotRigidBody2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_is_able_to_sleep
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_test_motion
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "test_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_test_motion #-}

instance Method "test_motion" GodotRigidBody2D
           (GodotVector2 ->
              Bool -> Float -> GodotPhysics2DTestMotionResult -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_test_motion (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D__direct_state_changed
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "_direct_state_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D__direct_state_changed #-}

instance Method "_direct_state_changed" GodotRigidBody2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D__direct_state_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D__body_enter_tree
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "_body_enter_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D__body_enter_tree #-}

instance Method "_body_enter_tree" GodotRigidBody2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D__body_enter_tree
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D__body_exit_tree
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "_body_exit_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D__body_exit_tree #-}

instance Method "_body_exit_tree" GodotRigidBody2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D__body_exit_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRigidBody2D_get_colliding_bodies
  = unsafePerformIO $
      withCString "RigidBody2D" $
        \ clsNamePtr ->
          withCString "get_colliding_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRigidBody2D_get_colliding_bodies #-}

instance Method "get_colliding_bodies" GodotRigidBody2D
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRigidBody2D_get_colliding_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotKinematicBody2D = GodotKinematicBody2D GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotKinematicBody2D where
        type BaseClass GodotKinematicBody2D = GodotPhysicsBody2D
        super = coerce
bindKinematicBody2D_move_and_collide
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "move_and_collide" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_move_and_collide #-}

instance Method "move_and_collide" GodotKinematicBody2D
           (GodotVector2 ->
              Bool -> Bool -> Bool -> IO GodotKinematicCollision2D)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_move_and_collide
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_move_and_slide
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "move_and_slide" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_move_and_slide #-}

instance Method "move_and_slide" GodotKinematicBody2D
           (GodotVector2 ->
              GodotVector2 -> Bool -> Bool -> Int -> Float -> IO GodotVector2)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_move_and_slide
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_move_and_slide_with_snap
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "move_and_slide_with_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_move_and_slide_with_snap #-}

instance Method "move_and_slide_with_snap" GodotKinematicBody2D
           (GodotVector2 ->
              GodotVector2 ->
                GodotVector2 -> Bool -> Bool -> Int -> Float -> IO GodotVector2)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_move_and_slide_with_snap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_test_move
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "test_move" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_test_move #-}

instance Method "test_move" GodotKinematicBody2D
           (GodotTransform2d -> GodotVector2 -> Bool -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_test_move (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_is_on_floor
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "is_on_floor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_is_on_floor #-}

instance Method "is_on_floor" GodotKinematicBody2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_is_on_floor (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_is_on_ceiling
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "is_on_ceiling" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_is_on_ceiling #-}

instance Method "is_on_ceiling" GodotKinematicBody2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_is_on_ceiling
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_is_on_wall
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "is_on_wall" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_is_on_wall #-}

instance Method "is_on_wall" GodotKinematicBody2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_is_on_wall (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_get_floor_velocity
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "get_floor_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_get_floor_velocity #-}

instance Method "get_floor_velocity" GodotKinematicBody2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_get_floor_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_set_safe_margin
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "set_safe_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_set_safe_margin #-}

instance Method "set_safe_margin" GodotKinematicBody2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_set_safe_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_get_safe_margin
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "get_safe_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_get_safe_margin #-}

instance Method "get_safe_margin" GodotKinematicBody2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_get_safe_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_get_slide_count
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "get_slide_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_get_slide_count #-}

instance Method "get_slide_count" GodotKinematicBody2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_get_slide_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_get_slide_collision
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "get_slide_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_get_slide_collision #-}

instance Method "get_slide_collision" GodotKinematicBody2D
           (Int -> IO GodotKinematicCollision2D)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_get_slide_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_set_sync_to_physics
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "set_sync_to_physics" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_set_sync_to_physics #-}

instance Method "set_sync_to_physics" GodotKinematicBody2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D_set_sync_to_physics
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D_is_sync_to_physics_enabled
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "is_sync_to_physics_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D_is_sync_to_physics_enabled #-}

instance Method "is_sync_to_physics_enabled" GodotKinematicBody2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindKinematicBody2D_is_sync_to_physics_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicBody2D__direct_state_changed
  = unsafePerformIO $
      withCString "KinematicBody2D" $
        \ clsNamePtr ->
          withCString "_direct_state_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicBody2D__direct_state_changed #-}

instance Method "_direct_state_changed" GodotKinematicBody2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicBody2D__direct_state_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotKinematicCollision2D = GodotKinematicCollision2D GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotKinematicCollision2D where
        type BaseClass GodotKinematicCollision2D = GodotReference
        super = coerce
bindKinematicCollision2D_get_position
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_position #-}

instance Method "get_position" GodotKinematicCollision2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_normal
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_normal #-}

instance Method "get_normal" GodotKinematicCollision2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_travel
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_travel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_travel #-}

instance Method "get_travel" GodotKinematicCollision2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_travel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_remainder
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_remainder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_remainder #-}

instance Method "get_remainder" GodotKinematicCollision2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_remainder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_local_shape
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_local_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_local_shape #-}

instance Method "get_local_shape" GodotKinematicCollision2D
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_local_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_collider
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_collider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_collider #-}

instance Method "get_collider" GodotKinematicCollision2D
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_collider
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_collider_id
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_collider_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_collider_id #-}

instance Method "get_collider_id" GodotKinematicCollision2D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_collider_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_collider_shape
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_collider_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_collider_shape #-}

instance Method "get_collider_shape" GodotKinematicCollision2D
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindKinematicCollision2D_get_collider_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_collider_shape_index
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_collider_shape_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_collider_shape_index #-}

instance Method "get_collider_shape_index"
           GodotKinematicCollision2D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindKinematicCollision2D_get_collider_shape_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_collider_velocity
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_collider_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_collider_velocity #-}

instance Method "get_collider_velocity" GodotKinematicCollision2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindKinematicCollision2D_get_collider_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindKinematicCollision2D_get_collider_metadata
  = unsafePerformIO $
      withCString "KinematicCollision2D" $
        \ clsNamePtr ->
          withCString "get_collider_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindKinematicCollision2D_get_collider_metadata #-}

instance Method "get_collider_metadata" GodotKinematicCollision2D
           (IO GodotVariant)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindKinematicCollision2D_get_collider_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotArea2D = GodotArea2D GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotArea2D where
        type BaseClass GodotArea2D = GodotCollisionObject2D
        super = coerce
bindArea2D__body_enter_tree
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "_body_enter_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D__body_enter_tree #-}

instance Method "_body_enter_tree" GodotArea2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D__body_enter_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D__body_exit_tree
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "_body_exit_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D__body_exit_tree #-}

instance Method "_body_exit_tree" GodotArea2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D__body_exit_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D__area_enter_tree
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "_area_enter_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D__area_enter_tree #-}

instance Method "_area_enter_tree" GodotArea2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D__area_enter_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D__area_exit_tree
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "_area_exit_tree" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D__area_exit_tree #-}

instance Method "_area_exit_tree" GodotArea2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D__area_exit_tree (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_space_override_mode
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_space_override_mode #-}

instance Method "set_space_override_mode" GodotArea2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_space_override_mode
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_space_override_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_space_override_mode #-}

instance Method "get_space_override_mode" GodotArea2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_space_override_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_gravity_is_point
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_gravity_is_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_gravity_is_point #-}

instance Method "set_gravity_is_point" GodotArea2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_gravity_is_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_is_gravity_a_point
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "is_gravity_a_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_is_gravity_a_point #-}

instance Method "is_gravity_a_point" GodotArea2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_is_gravity_a_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_gravity_distance_scale
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_gravity_distance_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_gravity_distance_scale #-}

instance Method "set_gravity_distance_scale" GodotArea2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_gravity_distance_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_gravity_distance_scale
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_gravity_distance_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_gravity_distance_scale #-}

instance Method "get_gravity_distance_scale" GodotArea2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_gravity_distance_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_gravity_vector
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_gravity_vector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_gravity_vector #-}

instance Method "set_gravity_vector" GodotArea2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_gravity_vector (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_gravity_vector
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_gravity_vector" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_gravity_vector #-}

instance Method "get_gravity_vector" GodotArea2D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_gravity_vector (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_gravity
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_gravity #-}

instance Method "set_gravity" GodotArea2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_gravity (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_gravity
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_gravity #-}

instance Method "get_gravity" GodotArea2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_gravity (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_linear_damp
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_linear_damp #-}

instance Method "set_linear_damp" GodotArea2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_linear_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_linear_damp
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_linear_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_linear_damp #-}

instance Method "get_linear_damp" GodotArea2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_linear_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_angular_damp
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_angular_damp #-}

instance Method "set_angular_damp" GodotArea2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_angular_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_angular_damp
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_angular_damp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_angular_damp #-}

instance Method "get_angular_damp" GodotArea2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_angular_damp (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_priority
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_priority #-}

instance Method "set_priority" GodotArea2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_priority (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_priority
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_priority #-}

instance Method "get_priority" GodotArea2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_priority (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_collision_mask
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_collision_mask #-}

instance Method "set_collision_mask" GodotArea2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_collision_mask
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_collision_mask #-}

instance Method "get_collision_mask" GodotArea2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_collision_layer
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_collision_layer #-}

instance Method "set_collision_layer" GodotArea2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_collision_layer
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_collision_layer #-}

instance Method "get_collision_layer" GodotArea2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_collision_mask_bit
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotArea2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_collision_mask_bit
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotArea2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_collision_layer_bit
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_collision_layer_bit #-}

instance Method "set_collision_layer_bit" GodotArea2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_collision_layer_bit
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_collision_layer_bit #-}

instance Method "get_collision_layer_bit" GodotArea2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_monitoring
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_monitoring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_monitoring #-}

instance Method "set_monitoring" GodotArea2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_monitoring (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_is_monitoring
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "is_monitoring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_is_monitoring #-}

instance Method "is_monitoring" GodotArea2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_is_monitoring (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_monitorable
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_monitorable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_monitorable #-}

instance Method "set_monitorable" GodotArea2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_monitorable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_is_monitorable
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "is_monitorable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_is_monitorable #-}

instance Method "is_monitorable" GodotArea2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_is_monitorable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_overlapping_bodies
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_overlapping_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_overlapping_bodies #-}

instance Method "get_overlapping_bodies" GodotArea2D
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_overlapping_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_overlapping_areas
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_overlapping_areas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_overlapping_areas #-}

instance Method "get_overlapping_areas" GodotArea2D (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_overlapping_areas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_overlaps_body
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "overlaps_body" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_overlaps_body #-}

instance Method "overlaps_body" GodotArea2D
           (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_overlaps_body (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_overlaps_area
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "overlaps_area" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_overlaps_area #-}

instance Method "overlaps_area" GodotArea2D
           (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_overlaps_area (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_audio_bus_name
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_audio_bus_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_audio_bus_name #-}

instance Method "set_audio_bus_name" GodotArea2D
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_audio_bus_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_get_audio_bus_name
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "get_audio_bus_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_get_audio_bus_name #-}

instance Method "get_audio_bus_name" GodotArea2D (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_get_audio_bus_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_set_audio_bus_override
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "set_audio_bus_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_set_audio_bus_override #-}

instance Method "set_audio_bus_override" GodotArea2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_set_audio_bus_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D_is_overriding_audio_bus
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "is_overriding_audio_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D_is_overriding_audio_bus #-}

instance Method "is_overriding_audio_bus" GodotArea2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D_is_overriding_audio_bus
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D__body_inout
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "_body_inout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D__body_inout #-}

instance Method "_body_inout" GodotArea2D
           (Int -> GodotRid -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D__body_inout (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArea2D__area_inout
  = unsafePerformIO $
      withCString "Area2D" $
        \ clsNamePtr ->
          withCString "_area_inout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArea2D__area_inout #-}

instance Method "_area_inout" GodotArea2D
           (Int -> GodotRid -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArea2D__area_inout (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCollisionShape2D = GodotCollisionShape2D GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotCollisionShape2D where
        type BaseClass GodotCollisionShape2D = GodotNode2D
        super = coerce
bindCollisionShape2D_set_shape
  = unsafePerformIO $
      withCString "CollisionShape2D" $
        \ clsNamePtr ->
          withCString "set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape2D_set_shape #-}

instance Method "set_shape" GodotCollisionShape2D
           (GodotShape2D -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape2D_set_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape2D_get_shape
  = unsafePerformIO $
      withCString "CollisionShape2D" $
        \ clsNamePtr ->
          withCString "get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape2D_get_shape #-}

instance Method "get_shape" GodotCollisionShape2D (IO GodotShape2D)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape2D_get_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape2D_set_disabled
  = unsafePerformIO $
      withCString "CollisionShape2D" $
        \ clsNamePtr ->
          withCString "set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape2D_set_disabled #-}

instance Method "set_disabled" GodotCollisionShape2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape2D_set_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape2D_is_disabled
  = unsafePerformIO $
      withCString "CollisionShape2D" $
        \ clsNamePtr ->
          withCString "is_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape2D_is_disabled #-}

instance Method "is_disabled" GodotCollisionShape2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape2D_is_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape2D_set_one_way_collision
  = unsafePerformIO $
      withCString "CollisionShape2D" $
        \ clsNamePtr ->
          withCString "set_one_way_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape2D_set_one_way_collision #-}

instance Method "set_one_way_collision" GodotCollisionShape2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape2D_set_one_way_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape2D_is_one_way_collision_enabled
  = unsafePerformIO $
      withCString "CollisionShape2D" $
        \ clsNamePtr ->
          withCString "is_one_way_collision_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape2D_is_one_way_collision_enabled #-}

instance Method "is_one_way_collision_enabled"
           GodotCollisionShape2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionShape2D_is_one_way_collision_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionShape2D__shape_changed
  = unsafePerformIO $
      withCString "CollisionShape2D" $
        \ clsNamePtr ->
          withCString "_shape_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionShape2D__shape_changed #-}

instance Method "_shape_changed" GodotCollisionShape2D (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionShape2D__shape_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotShape2D = GodotShape2D GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotShape2D where
        type BaseClass GodotShape2D = GodotResource
        super = coerce
bindShape2D_set_custom_solver_bias
  = unsafePerformIO $
      withCString "Shape2D" $
        \ clsNamePtr ->
          withCString "set_custom_solver_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape2D_set_custom_solver_bias #-}

instance Method "set_custom_solver_bias" GodotShape2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShape2D_set_custom_solver_bias
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShape2D_get_custom_solver_bias
  = unsafePerformIO $
      withCString "Shape2D" $
        \ clsNamePtr ->
          withCString "get_custom_solver_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape2D_get_custom_solver_bias #-}

instance Method "get_custom_solver_bias" GodotShape2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShape2D_get_custom_solver_bias
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShape2D_collide
  = unsafePerformIO $
      withCString "Shape2D" $
        \ clsNamePtr ->
          withCString "collide" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape2D_collide #-}

instance Method "collide" GodotShape2D
           (GodotTransform2d -> GodotShape2D -> GodotTransform2d -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShape2D_collide (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShape2D_collide_with_motion
  = unsafePerformIO $
      withCString "Shape2D" $
        \ clsNamePtr ->
          withCString "collide_with_motion" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape2D_collide_with_motion #-}

instance Method "collide_with_motion" GodotShape2D
           (GodotTransform2d ->
              GodotVector2 ->
                GodotShape2D -> GodotTransform2d -> GodotVector2 -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShape2D_collide_with_motion (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShape2D_collide_and_get_contacts
  = unsafePerformIO $
      withCString "Shape2D" $
        \ clsNamePtr ->
          withCString "collide_and_get_contacts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape2D_collide_and_get_contacts #-}

instance Method "collide_and_get_contacts" GodotShape2D
           (GodotTransform2d ->
              GodotShape2D -> GodotTransform2d -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindShape2D_collide_and_get_contacts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindShape2D_collide_with_motion_and_get_contacts
  = unsafePerformIO $
      withCString "Shape2D" $
        \ clsNamePtr ->
          withCString "collide_with_motion_and_get_contacts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindShape2D_collide_with_motion_and_get_contacts #-}

instance Method "collide_with_motion_and_get_contacts" GodotShape2D
           (GodotTransform2d ->
              GodotVector2 ->
                GodotShape2D ->
                  GodotTransform2d -> GodotVector2 -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindShape2D_collide_with_motion_and_get_contacts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCollisionPolygon2D = GodotCollisionPolygon2D GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotCollisionPolygon2D where
        type BaseClass GodotCollisionPolygon2D = GodotNode2D
        super = coerce
bindCollisionPolygon2D_set_polygon
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "set_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_set_polygon #-}

instance Method "set_polygon" GodotCollisionPolygon2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon2D_set_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon2D_get_polygon
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "get_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_get_polygon #-}

instance Method "get_polygon" GodotCollisionPolygon2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon2D_get_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon2D_set_build_mode
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "set_build_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_set_build_mode #-}

instance Method "set_build_mode" GodotCollisionPolygon2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon2D_set_build_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon2D_get_build_mode
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "get_build_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_get_build_mode #-}

instance Method "get_build_mode" GodotCollisionPolygon2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon2D_get_build_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon2D_set_disabled
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "set_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_set_disabled #-}

instance Method "set_disabled" GodotCollisionPolygon2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon2D_set_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon2D_is_disabled
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "is_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_is_disabled #-}

instance Method "is_disabled" GodotCollisionPolygon2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon2D_is_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon2D_set_one_way_collision
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "set_one_way_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_set_one_way_collision #-}

instance Method "set_one_way_collision" GodotCollisionPolygon2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCollisionPolygon2D_set_one_way_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCollisionPolygon2D_is_one_way_collision_enabled
  = unsafePerformIO $
      withCString "CollisionPolygon2D" $
        \ clsNamePtr ->
          withCString "is_one_way_collision_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCollisionPolygon2D_is_one_way_collision_enabled
             #-}

instance Method "is_one_way_collision_enabled"
           GodotCollisionPolygon2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCollisionPolygon2D_is_one_way_collision_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRayCast2D = GodotRayCast2D GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotRayCast2D where
        type BaseClass GodotRayCast2D = GodotNode2D
        super = coerce
bindRayCast2D_set_enabled
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_set_enabled #-}

instance Method "set_enabled" GodotRayCast2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_set_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_is_enabled
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_is_enabled #-}

instance Method "is_enabled" GodotRayCast2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_is_enabled (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_set_cast_to
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "set_cast_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_set_cast_to #-}

instance Method "set_cast_to" GodotRayCast2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_set_cast_to (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_cast_to
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_cast_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_cast_to #-}

instance Method "get_cast_to" GodotRayCast2D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_cast_to (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_is_colliding
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "is_colliding" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_is_colliding #-}

instance Method "is_colliding" GodotRayCast2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_is_colliding (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_force_raycast_update
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "force_raycast_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_force_raycast_update #-}

instance Method "force_raycast_update" GodotRayCast2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_force_raycast_update
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_collider
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_collider" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_collider #-}

instance Method "get_collider" GodotRayCast2D (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_collider (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_collider_shape
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_collider_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_collider_shape #-}

instance Method "get_collider_shape" GodotRayCast2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_collider_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_collision_point
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_collision_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_collision_point #-}

instance Method "get_collision_point" GodotRayCast2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_collision_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_collision_normal
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_collision_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_collision_normal #-}

instance Method "get_collision_normal" GodotRayCast2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_collision_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_add_exception_rid
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "add_exception_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_add_exception_rid #-}

instance Method "add_exception_rid" GodotRayCast2D
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_add_exception_rid (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_add_exception
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "add_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_add_exception #-}

instance Method "add_exception" GodotRayCast2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_add_exception (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_remove_exception_rid
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "remove_exception_rid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_remove_exception_rid #-}

instance Method "remove_exception_rid" GodotRayCast2D
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_remove_exception_rid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_remove_exception
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "remove_exception" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_remove_exception #-}

instance Method "remove_exception" GodotRayCast2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_remove_exception (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_clear_exceptions
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "clear_exceptions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_clear_exceptions #-}

instance Method "clear_exceptions" GodotRayCast2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_clear_exceptions (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_set_collision_mask
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_set_collision_mask #-}

instance Method "set_collision_mask" GodotRayCast2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_set_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_collision_mask
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_collision_mask #-}

instance Method "get_collision_mask" GodotRayCast2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_collision_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_set_collision_mask_bit
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotRayCast2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_collision_mask_bit
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotRayCast2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_set_exclude_parent_body
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "set_exclude_parent_body" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_set_exclude_parent_body #-}

instance Method "set_exclude_parent_body" GodotRayCast2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_set_exclude_parent_body
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_get_exclude_parent_body
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "get_exclude_parent_body" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_get_exclude_parent_body #-}

instance Method "get_exclude_parent_body" GodotRayCast2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_get_exclude_parent_body
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_set_collide_with_areas
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "set_collide_with_areas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_set_collide_with_areas #-}

instance Method "set_collide_with_areas" GodotRayCast2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_set_collide_with_areas
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_is_collide_with_areas_enabled
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "is_collide_with_areas_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_is_collide_with_areas_enabled #-}

instance Method "is_collide_with_areas_enabled" GodotRayCast2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_is_collide_with_areas_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_set_collide_with_bodies
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "set_collide_with_bodies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_set_collide_with_bodies #-}

instance Method "set_collide_with_bodies" GodotRayCast2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_set_collide_with_bodies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayCast2D_is_collide_with_bodies_enabled
  = unsafePerformIO $
      withCString "RayCast2D" $
        \ clsNamePtr ->
          withCString "is_collide_with_bodies_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayCast2D_is_collide_with_bodies_enabled #-}

instance Method "is_collide_with_bodies_enabled" GodotRayCast2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayCast2D_is_collide_with_bodies_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisibilityNotifier2D = GodotVisibilityNotifier2D GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisibilityNotifier2D where
        type BaseClass GodotVisibilityNotifier2D = GodotNode2D
        super = coerce
bindVisibilityNotifier2D_set_rect
  = unsafePerformIO $
      withCString "VisibilityNotifier2D" $
        \ clsNamePtr ->
          withCString "set_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityNotifier2D_set_rect #-}

instance Method "set_rect" GodotVisibilityNotifier2D
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityNotifier2D_set_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityNotifier2D_get_rect
  = unsafePerformIO $
      withCString "VisibilityNotifier2D" $
        \ clsNamePtr ->
          withCString "get_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityNotifier2D_get_rect #-}

instance Method "get_rect" GodotVisibilityNotifier2D
           (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityNotifier2D_get_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityNotifier2D_is_on_screen
  = unsafePerformIO $
      withCString "VisibilityNotifier2D" $
        \ clsNamePtr ->
          withCString "is_on_screen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityNotifier2D_is_on_screen #-}

instance Method "is_on_screen" GodotVisibilityNotifier2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityNotifier2D_is_on_screen
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisibilityEnabler2D = GodotVisibilityEnabler2D GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotVisibilityEnabler2D where
        type BaseClass GodotVisibilityEnabler2D = GodotVisibilityNotifier2D
        super = coerce
bindVisibilityEnabler2D_set_enabler
  = unsafePerformIO $
      withCString "VisibilityEnabler2D" $
        \ clsNamePtr ->
          withCString "set_enabler" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityEnabler2D_set_enabler #-}

instance Method "set_enabler" GodotVisibilityEnabler2D
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityEnabler2D_set_enabler
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityEnabler2D_is_enabler_enabled
  = unsafePerformIO $
      withCString "VisibilityEnabler2D" $
        \ clsNamePtr ->
          withCString "is_enabler_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityEnabler2D_is_enabler_enabled #-}

instance Method "is_enabler_enabled" GodotVisibilityEnabler2D
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityEnabler2D_is_enabler_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisibilityEnabler2D__node_removed
  = unsafePerformIO $
      withCString "VisibilityEnabler2D" $
        \ clsNamePtr ->
          withCString "_node_removed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisibilityEnabler2D__node_removed #-}

instance Method "_node_removed" GodotVisibilityEnabler2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisibilityEnabler2D__node_removed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPolygon2D = GodotPolygon2D GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotPolygon2D where
        type BaseClass GodotPolygon2D = GodotNode2D
        super = coerce
bindPolygon2D_set_polygon
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_polygon #-}

instance Method "set_polygon" GodotPolygon2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_polygon
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_polygon #-}

instance Method "get_polygon" GodotPolygon2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_uv
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_uv #-}

instance Method "set_uv" GodotPolygon2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_uv (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_uv
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_uv #-}

instance Method "get_uv" GodotPolygon2D (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_uv (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_color
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_color #-}

instance Method "set_color" GodotPolygon2D (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_color
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_color #-}

instance Method "get_color" GodotPolygon2D (IO GodotColor) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_splits
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_splits" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_splits #-}

instance Method "set_splits" GodotPolygon2D
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_splits (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_splits
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_splits" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_splits #-}

instance Method "get_splits" GodotPolygon2D (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_splits (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_vertex_colors
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_vertex_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_vertex_colors #-}

instance Method "set_vertex_colors" GodotPolygon2D
           (GodotPoolColorArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_vertex_colors (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_vertex_colors
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_vertex_colors" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_vertex_colors #-}

instance Method "get_vertex_colors" GodotPolygon2D
           (IO GodotPoolColorArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_vertex_colors (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_texture
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_texture #-}

instance Method "set_texture" GodotPolygon2D
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_texture
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_texture #-}

instance Method "get_texture" GodotPolygon2D (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_texture_offset
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_texture_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_texture_offset #-}

instance Method "set_texture_offset" GodotPolygon2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_texture_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_texture_offset
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_texture_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_texture_offset #-}

instance Method "get_texture_offset" GodotPolygon2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_texture_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_texture_rotation
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_texture_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_texture_rotation #-}

instance Method "set_texture_rotation" GodotPolygon2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_texture_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_texture_rotation
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_texture_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_texture_rotation #-}

instance Method "get_texture_rotation" GodotPolygon2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_texture_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_texture_rotation_degrees
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_texture_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_texture_rotation_degrees #-}

instance Method "set_texture_rotation_degrees" GodotPolygon2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_texture_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_texture_rotation_degrees
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_texture_rotation_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_texture_rotation_degrees #-}

instance Method "get_texture_rotation_degrees" GodotPolygon2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_texture_rotation_degrees
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_texture_scale
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_texture_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_texture_scale #-}

instance Method "set_texture_scale" GodotPolygon2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_texture_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_texture_scale
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_texture_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_texture_scale #-}

instance Method "get_texture_scale" GodotPolygon2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_texture_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_invert
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_invert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_invert #-}

instance Method "set_invert" GodotPolygon2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_invert (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_invert
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_invert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_invert #-}

instance Method "get_invert" GodotPolygon2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_invert (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_antialiased
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_antialiased" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_antialiased #-}

instance Method "set_antialiased" GodotPolygon2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_antialiased (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_antialiased
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_antialiased" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_antialiased #-}

instance Method "get_antialiased" GodotPolygon2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_antialiased (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_invert_border
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_invert_border" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_invert_border #-}

instance Method "set_invert_border" GodotPolygon2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_invert_border (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_invert_border
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_invert_border" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_invert_border #-}

instance Method "get_invert_border" GodotPolygon2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_invert_border (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_offset
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_offset #-}

instance Method "set_offset" GodotPolygon2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_offset
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_offset #-}

instance Method "get_offset" GodotPolygon2D (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_add_bone
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "add_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_add_bone #-}

instance Method "add_bone" GodotPolygon2D
           (GodotNodePath -> GodotPoolRealArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_add_bone (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_bone_count
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_bone_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_bone_count #-}

instance Method "get_bone_count" GodotPolygon2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_bone_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_bone_path
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_bone_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_bone_path #-}

instance Method "get_bone_path" GodotPolygon2D
           (Int -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_bone_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_bone_weights
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_bone_weights" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_bone_weights #-}

instance Method "get_bone_weights" GodotPolygon2D
           (Int -> IO GodotPoolRealArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_bone_weights (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_erase_bone
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "erase_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_erase_bone #-}

instance Method "erase_bone" GodotPolygon2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_erase_bone (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_clear_bones
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "clear_bones" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_clear_bones #-}

instance Method "clear_bones" GodotPolygon2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_clear_bones (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_bone_path
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_bone_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_bone_path #-}

instance Method "set_bone_path" GodotPolygon2D
           (Int -> GodotNodePath -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_bone_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_bone_weights
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_bone_weights" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_bone_weights #-}

instance Method "set_bone_weights" GodotPolygon2D
           (Int -> GodotPoolRealArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_bone_weights (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_set_skeleton
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "set_skeleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_set_skeleton #-}

instance Method "set_skeleton" GodotPolygon2D
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_set_skeleton (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D_get_skeleton
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "get_skeleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D_get_skeleton #-}

instance Method "get_skeleton" GodotPolygon2D (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D_get_skeleton (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D__set_bones
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "_set_bones" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D__set_bones #-}

instance Method "_set_bones" GodotPolygon2D (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D__set_bones (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygon2D__get_bones
  = unsafePerformIO $
      withCString "Polygon2D" $
        \ clsNamePtr ->
          withCString "_get_bones" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygon2D__get_bones #-}

instance Method "_get_bones" GodotPolygon2D (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygon2D__get_bones (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSkeleton2D = GodotSkeleton2D GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotSkeleton2D where
        type BaseClass GodotSkeleton2D = GodotNode2D
        super = coerce
bindSkeleton2D__update_bone_setup
  = unsafePerformIO $
      withCString "Skeleton2D" $
        \ clsNamePtr ->
          withCString "_update_bone_setup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton2D__update_bone_setup #-}

instance Method "_update_bone_setup" GodotSkeleton2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton2D__update_bone_setup
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton2D__update_transform
  = unsafePerformIO $
      withCString "Skeleton2D" $
        \ clsNamePtr ->
          withCString "_update_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton2D__update_transform #-}

instance Method "_update_transform" GodotSkeleton2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton2D__update_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton2D_get_bone_count
  = unsafePerformIO $
      withCString "Skeleton2D" $
        \ clsNamePtr ->
          withCString "get_bone_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton2D_get_bone_count #-}

instance Method "get_bone_count" GodotSkeleton2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton2D_get_bone_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton2D_get_bone
  = unsafePerformIO $
      withCString "Skeleton2D" $
        \ clsNamePtr ->
          withCString "get_bone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton2D_get_bone #-}

instance Method "get_bone" GodotSkeleton2D (Int -> IO GodotBone2D)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton2D_get_bone (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSkeleton2D_get_skeleton
  = unsafePerformIO $
      withCString "Skeleton2D" $
        \ clsNamePtr ->
          withCString "get_skeleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSkeleton2D_get_skeleton #-}

instance Method "get_skeleton" GodotSkeleton2D (IO GodotRid) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSkeleton2D_get_skeleton (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBone2D = GodotBone2D GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotBone2D where
        type BaseClass GodotBone2D = GodotNode2D
        super = coerce
bindBone2D_set_rest
  = unsafePerformIO $
      withCString "Bone2D" $
        \ clsNamePtr ->
          withCString "set_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBone2D_set_rest #-}

instance Method "set_rest" GodotBone2D (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBone2D_set_rest (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBone2D_get_rest
  = unsafePerformIO $
      withCString "Bone2D" $
        \ clsNamePtr ->
          withCString "get_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBone2D_get_rest #-}

instance Method "get_rest" GodotBone2D (IO GodotTransform2d) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBone2D_get_rest (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBone2D_apply_rest
  = unsafePerformIO $
      withCString "Bone2D" $
        \ clsNamePtr ->
          withCString "apply_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBone2D_apply_rest #-}

instance Method "apply_rest" GodotBone2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBone2D_apply_rest (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBone2D_get_skeleton_rest
  = unsafePerformIO $
      withCString "Bone2D" $
        \ clsNamePtr ->
          withCString "get_skeleton_rest" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBone2D_get_skeleton_rest #-}

instance Method "get_skeleton_rest" GodotBone2D
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBone2D_get_skeleton_rest (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBone2D_get_index_in_skeleton
  = unsafePerformIO $
      withCString "Bone2D" $
        \ clsNamePtr ->
          withCString "get_index_in_skeleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBone2D_get_index_in_skeleton #-}

instance Method "get_index_in_skeleton" GodotBone2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBone2D_get_index_in_skeleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBone2D_set_default_length
  = unsafePerformIO $
      withCString "Bone2D" $
        \ clsNamePtr ->
          withCString "set_default_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBone2D_set_default_length #-}

instance Method "set_default_length" GodotBone2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBone2D_set_default_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBone2D_get_default_length
  = unsafePerformIO $
      withCString "Bone2D" $
        \ clsNamePtr ->
          withCString "get_default_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBone2D_get_default_length #-}

instance Method "get_default_length" GodotBone2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBone2D_get_default_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotLight2D = GodotLight2D GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotLight2D where
        type BaseClass GodotLight2D = GodotNode2D
        super = coerce
bindLight2D_set_enabled
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_enabled #-}

instance Method "set_enabled" GodotLight2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_enabled (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_is_enabled
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_is_enabled #-}

instance Method "is_enabled" GodotLight2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_is_enabled (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_editor_only
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_editor_only" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_editor_only #-}

instance Method "set_editor_only" GodotLight2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_editor_only (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_is_editor_only
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "is_editor_only" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_is_editor_only #-}

instance Method "is_editor_only" GodotLight2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_is_editor_only (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_texture
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_texture #-}

instance Method "set_texture" GodotLight2D (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_texture
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_texture #-}

instance Method "get_texture" GodotLight2D (IO GodotTexture) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_texture (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_texture_offset
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_texture_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_texture_offset #-}

instance Method "set_texture_offset" GodotLight2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_texture_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_texture_offset
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_texture_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_texture_offset #-}

instance Method "get_texture_offset" GodotLight2D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_texture_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_color
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_color #-}

instance Method "set_color" GodotLight2D (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_color
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_color #-}

instance Method "get_color" GodotLight2D (IO GodotColor) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_color (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_height
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_height #-}

instance Method "set_height" GodotLight2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_height (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_height
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_height #-}

instance Method "get_height" GodotLight2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_height (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_energy
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_energy #-}

instance Method "set_energy" GodotLight2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_energy (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_energy
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_energy #-}

instance Method "get_energy" GodotLight2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_energy (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_texture_scale
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_texture_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_texture_scale #-}

instance Method "set_texture_scale" GodotLight2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_texture_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_texture_scale
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_texture_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_texture_scale #-}

instance Method "get_texture_scale" GodotLight2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_texture_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_z_range_min
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_z_range_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_z_range_min #-}

instance Method "set_z_range_min" GodotLight2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_z_range_min (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_z_range_min
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_z_range_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_z_range_min #-}

instance Method "get_z_range_min" GodotLight2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_z_range_min (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_z_range_max
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_z_range_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_z_range_max #-}

instance Method "set_z_range_max" GodotLight2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_z_range_max (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_z_range_max
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_z_range_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_z_range_max #-}

instance Method "get_z_range_max" GodotLight2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_z_range_max (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_layer_range_min
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_layer_range_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_layer_range_min #-}

instance Method "set_layer_range_min" GodotLight2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_layer_range_min (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_layer_range_min
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_layer_range_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_layer_range_min #-}

instance Method "get_layer_range_min" GodotLight2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_layer_range_min (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_layer_range_max
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_layer_range_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_layer_range_max #-}

instance Method "set_layer_range_max" GodotLight2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_layer_range_max (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_layer_range_max
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_layer_range_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_layer_range_max #-}

instance Method "get_layer_range_max" GodotLight2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_layer_range_max (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_item_cull_mask
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_item_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_item_cull_mask #-}

instance Method "set_item_cull_mask" GodotLight2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_item_cull_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_item_cull_mask
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_item_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_item_cull_mask #-}

instance Method "get_item_cull_mask" GodotLight2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_item_cull_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_item_shadow_cull_mask
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_item_shadow_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_item_shadow_cull_mask #-}

instance Method "set_item_shadow_cull_mask" GodotLight2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_item_shadow_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_item_shadow_cull_mask
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_item_shadow_cull_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_item_shadow_cull_mask #-}

instance Method "get_item_shadow_cull_mask" GodotLight2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_item_shadow_cull_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_mode
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_mode #-}

instance Method "set_mode" GodotLight2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_mode (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_mode
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_mode #-}

instance Method "get_mode" GodotLight2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_mode (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_shadow_enabled
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_shadow_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_shadow_enabled #-}

instance Method "set_shadow_enabled" GodotLight2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_shadow_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_is_shadow_enabled
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "is_shadow_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_is_shadow_enabled #-}

instance Method "is_shadow_enabled" GodotLight2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_is_shadow_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_shadow_buffer_size
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_shadow_buffer_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_shadow_buffer_size #-}

instance Method "set_shadow_buffer_size" GodotLight2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_shadow_buffer_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_shadow_buffer_size
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_shadow_buffer_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_shadow_buffer_size #-}

instance Method "get_shadow_buffer_size" GodotLight2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_shadow_buffer_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_shadow_smooth
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_shadow_smooth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_shadow_smooth #-}

instance Method "set_shadow_smooth" GodotLight2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_shadow_smooth (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_shadow_smooth
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_shadow_smooth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_shadow_smooth #-}

instance Method "get_shadow_smooth" GodotLight2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_shadow_smooth (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_shadow_gradient_length
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_shadow_gradient_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_shadow_gradient_length #-}

instance Method "set_shadow_gradient_length" GodotLight2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_shadow_gradient_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_shadow_gradient_length
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_shadow_gradient_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_shadow_gradient_length #-}

instance Method "get_shadow_gradient_length" GodotLight2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_shadow_gradient_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_shadow_filter
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_shadow_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_shadow_filter #-}

instance Method "set_shadow_filter" GodotLight2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_shadow_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_shadow_filter
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_shadow_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_shadow_filter #-}

instance Method "get_shadow_filter" GodotLight2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_shadow_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_set_shadow_color
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "set_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_set_shadow_color #-}

instance Method "set_shadow_color" GodotLight2D
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_set_shadow_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLight2D_get_shadow_color
  = unsafePerformIO $
      withCString "Light2D" $
        \ clsNamePtr ->
          withCString "get_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLight2D_get_shadow_color #-}

instance Method "get_shadow_color" GodotLight2D (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLight2D_get_shadow_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotLightOccluder2D = GodotLightOccluder2D GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotLightOccluder2D where
        type BaseClass GodotLightOccluder2D = GodotNode2D
        super = coerce
bindLightOccluder2D_set_occluder_polygon
  = unsafePerformIO $
      withCString "LightOccluder2D" $
        \ clsNamePtr ->
          withCString "set_occluder_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLightOccluder2D_set_occluder_polygon #-}

instance Method "set_occluder_polygon" GodotLightOccluder2D
           (GodotOccluderPolygon2D -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLightOccluder2D_set_occluder_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLightOccluder2D_get_occluder_polygon
  = unsafePerformIO $
      withCString "LightOccluder2D" $
        \ clsNamePtr ->
          withCString "get_occluder_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLightOccluder2D_get_occluder_polygon #-}

instance Method "get_occluder_polygon" GodotLightOccluder2D
           (IO GodotOccluderPolygon2D)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLightOccluder2D_get_occluder_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLightOccluder2D_set_occluder_light_mask
  = unsafePerformIO $
      withCString "LightOccluder2D" $
        \ clsNamePtr ->
          withCString "set_occluder_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLightOccluder2D_set_occluder_light_mask #-}

instance Method "set_occluder_light_mask" GodotLightOccluder2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLightOccluder2D_set_occluder_light_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLightOccluder2D_get_occluder_light_mask
  = unsafePerformIO $
      withCString "LightOccluder2D" $
        \ clsNamePtr ->
          withCString "get_occluder_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLightOccluder2D_get_occluder_light_mask #-}

instance Method "get_occluder_light_mask" GodotLightOccluder2D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLightOccluder2D_get_occluder_light_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLightOccluder2D__poly_changed
  = unsafePerformIO $
      withCString "LightOccluder2D" $
        \ clsNamePtr ->
          withCString "_poly_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLightOccluder2D__poly_changed #-}

instance Method "_poly_changed" GodotLightOccluder2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLightOccluder2D__poly_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotOccluderPolygon2D = GodotOccluderPolygon2D GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotOccluderPolygon2D where
        type BaseClass GodotOccluderPolygon2D = GodotResource
        super = coerce
bindOccluderPolygon2D_set_closed
  = unsafePerformIO $
      withCString "OccluderPolygon2D" $
        \ clsNamePtr ->
          withCString "set_closed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOccluderPolygon2D_set_closed #-}

instance Method "set_closed" GodotOccluderPolygon2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOccluderPolygon2D_set_closed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOccluderPolygon2D_is_closed
  = unsafePerformIO $
      withCString "OccluderPolygon2D" $
        \ clsNamePtr ->
          withCString "is_closed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOccluderPolygon2D_is_closed #-}

instance Method "is_closed" GodotOccluderPolygon2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOccluderPolygon2D_is_closed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOccluderPolygon2D_set_cull_mode
  = unsafePerformIO $
      withCString "OccluderPolygon2D" $
        \ clsNamePtr ->
          withCString "set_cull_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOccluderPolygon2D_set_cull_mode #-}

instance Method "set_cull_mode" GodotOccluderPolygon2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOccluderPolygon2D_set_cull_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOccluderPolygon2D_get_cull_mode
  = unsafePerformIO $
      withCString "OccluderPolygon2D" $
        \ clsNamePtr ->
          withCString "get_cull_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOccluderPolygon2D_get_cull_mode #-}

instance Method "get_cull_mode" GodotOccluderPolygon2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOccluderPolygon2D_get_cull_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOccluderPolygon2D_set_polygon
  = unsafePerformIO $
      withCString "OccluderPolygon2D" $
        \ clsNamePtr ->
          withCString "set_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOccluderPolygon2D_set_polygon #-}

instance Method "set_polygon" GodotOccluderPolygon2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOccluderPolygon2D_set_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOccluderPolygon2D_get_polygon
  = unsafePerformIO $
      withCString "OccluderPolygon2D" $
        \ clsNamePtr ->
          withCString "get_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOccluderPolygon2D_get_polygon #-}

instance Method "get_polygon" GodotOccluderPolygon2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOccluderPolygon2D_get_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotYSort = GodotYSort GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotYSort where
        type BaseClass GodotYSort = GodotNode2D
        super = coerce
bindYSort_set_sort_enabled
  = unsafePerformIO $
      withCString "YSort" $
        \ clsNamePtr ->
          withCString "set_sort_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindYSort_set_sort_enabled #-}

instance Method "set_sort_enabled" GodotYSort (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindYSort_set_sort_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindYSort_is_sort_enabled
  = unsafePerformIO $
      withCString "YSort" $
        \ clsNamePtr ->
          withCString "is_sort_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindYSort_is_sort_enabled #-}

instance Method "is_sort_enabled" GodotYSort (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindYSort_is_sort_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBackBufferCopy = GodotBackBufferCopy GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotBackBufferCopy where
        type BaseClass GodotBackBufferCopy = GodotNode2D
        super = coerce
bindBackBufferCopy_set_rect
  = unsafePerformIO $
      withCString "BackBufferCopy" $
        \ clsNamePtr ->
          withCString "set_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBackBufferCopy_set_rect #-}

instance Method "set_rect" GodotBackBufferCopy
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBackBufferCopy_set_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBackBufferCopy_get_rect
  = unsafePerformIO $
      withCString "BackBufferCopy" $
        \ clsNamePtr ->
          withCString "get_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBackBufferCopy_get_rect #-}

instance Method "get_rect" GodotBackBufferCopy (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBackBufferCopy_get_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBackBufferCopy_set_copy_mode
  = unsafePerformIO $
      withCString "BackBufferCopy" $
        \ clsNamePtr ->
          withCString "set_copy_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBackBufferCopy_set_copy_mode #-}

instance Method "set_copy_mode" GodotBackBufferCopy (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBackBufferCopy_set_copy_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBackBufferCopy_get_copy_mode
  = unsafePerformIO $
      withCString "BackBufferCopy" $
        \ clsNamePtr ->
          withCString "get_copy_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBackBufferCopy_get_copy_mode #-}

instance Method "get_copy_mode" GodotBackBufferCopy (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBackBufferCopy_get_copy_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCamera2D = GodotCamera2D GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotCamera2D where
        type BaseClass GodotCamera2D = GodotNode2D
        super = coerce
bindCamera2D_set_offset
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_offset #-}

instance Method "set_offset" GodotCamera2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_offset
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_offset #-}

instance Method "get_offset" GodotCamera2D (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_anchor_mode
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_anchor_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_anchor_mode #-}

instance Method "set_anchor_mode" GodotCamera2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_anchor_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_anchor_mode
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_anchor_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_anchor_mode #-}

instance Method "get_anchor_mode" GodotCamera2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_anchor_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_rotating
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_rotating" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_rotating #-}

instance Method "set_rotating" GodotCamera2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_rotating (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_rotating
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_rotating" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_rotating #-}

instance Method "is_rotating" GodotCamera2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_rotating (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_make_current
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "make_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_make_current #-}

instance Method "make_current" GodotCamera2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_make_current (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_clear_current
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "clear_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_clear_current #-}

instance Method "clear_current" GodotCamera2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_clear_current (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D__make_current
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "_make_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D__make_current #-}

instance Method "_make_current" GodotCamera2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D__make_current (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D__update_scroll
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "_update_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D__update_scroll #-}

instance Method "_update_scroll" GodotCamera2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D__update_scroll (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D__set_current
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "_set_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D__set_current #-}

instance Method "_set_current" GodotCamera2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D__set_current (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_current
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_current" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_current #-}

instance Method "is_current" GodotCamera2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_current (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_limit
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_limit #-}

instance Method "set_limit" GodotCamera2D (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_limit (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_limit
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_limit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_limit #-}

instance Method "get_limit" GodotCamera2D (Int -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_limit (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_limit_smoothing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_limit_smoothing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_limit_smoothing_enabled #-}

instance Method "set_limit_smoothing_enabled" GodotCamera2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_limit_smoothing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_limit_smoothing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_limit_smoothing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_limit_smoothing_enabled #-}

instance Method "is_limit_smoothing_enabled" GodotCamera2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_limit_smoothing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_v_drag_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_v_drag_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_v_drag_enabled #-}

instance Method "set_v_drag_enabled" GodotCamera2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_v_drag_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_v_drag_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_v_drag_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_v_drag_enabled #-}

instance Method "is_v_drag_enabled" GodotCamera2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_v_drag_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_h_drag_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_h_drag_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_h_drag_enabled #-}

instance Method "set_h_drag_enabled" GodotCamera2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_h_drag_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_h_drag_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_h_drag_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_h_drag_enabled #-}

instance Method "is_h_drag_enabled" GodotCamera2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_h_drag_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_v_offset
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_v_offset #-}

instance Method "set_v_offset" GodotCamera2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_v_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_v_offset
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_v_offset #-}

instance Method "get_v_offset" GodotCamera2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_v_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_h_offset
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_h_offset #-}

instance Method "set_h_offset" GodotCamera2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_h_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_h_offset
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_h_offset #-}

instance Method "get_h_offset" GodotCamera2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_h_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_drag_margin
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_drag_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_drag_margin #-}

instance Method "set_drag_margin" GodotCamera2D
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_drag_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_drag_margin
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_drag_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_drag_margin #-}

instance Method "get_drag_margin" GodotCamera2D (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_drag_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_camera_position
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_camera_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_camera_position #-}

instance Method "get_camera_position" GodotCamera2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_camera_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_camera_screen_center
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_camera_screen_center" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_camera_screen_center #-}

instance Method "get_camera_screen_center" GodotCamera2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_camera_screen_center
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_zoom
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_zoom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_zoom #-}

instance Method "set_zoom" GodotCamera2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_zoom (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_zoom
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_zoom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_zoom #-}

instance Method "get_zoom" GodotCamera2D (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_zoom (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_custom_viewport
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_custom_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_custom_viewport #-}

instance Method "set_custom_viewport" GodotCamera2D
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_custom_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_custom_viewport
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_custom_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_custom_viewport #-}

instance Method "get_custom_viewport" GodotCamera2D (IO GodotNode)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_custom_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_follow_smoothing
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_follow_smoothing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_follow_smoothing #-}

instance Method "set_follow_smoothing" GodotCamera2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_follow_smoothing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_get_follow_smoothing
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "get_follow_smoothing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_get_follow_smoothing #-}

instance Method "get_follow_smoothing" GodotCamera2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_get_follow_smoothing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_enable_follow_smoothing
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_enable_follow_smoothing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_enable_follow_smoothing #-}

instance Method "set_enable_follow_smoothing" GodotCamera2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_enable_follow_smoothing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_follow_smoothing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_follow_smoothing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_follow_smoothing_enabled #-}

instance Method "is_follow_smoothing_enabled" GodotCamera2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_follow_smoothing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_force_update_scroll
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "force_update_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_force_update_scroll #-}

instance Method "force_update_scroll" GodotCamera2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_force_update_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_reset_smoothing
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "reset_smoothing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_reset_smoothing #-}

instance Method "reset_smoothing" GodotCamera2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_reset_smoothing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_align
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "align" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_align #-}

instance Method "align" GodotCamera2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_align (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D__set_old_smoothing
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "_set_old_smoothing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D__set_old_smoothing #-}

instance Method "_set_old_smoothing" GodotCamera2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D__set_old_smoothing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_screen_drawing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_screen_drawing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_screen_drawing_enabled #-}

instance Method "set_screen_drawing_enabled" GodotCamera2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_screen_drawing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_screen_drawing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_screen_drawing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_screen_drawing_enabled #-}

instance Method "is_screen_drawing_enabled" GodotCamera2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_screen_drawing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_limit_drawing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_limit_drawing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_limit_drawing_enabled #-}

instance Method "set_limit_drawing_enabled" GodotCamera2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_limit_drawing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_limit_drawing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_limit_drawing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_limit_drawing_enabled #-}

instance Method "is_limit_drawing_enabled" GodotCamera2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_limit_drawing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_set_margin_drawing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "set_margin_drawing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_set_margin_drawing_enabled #-}

instance Method "set_margin_drawing_enabled" GodotCamera2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_set_margin_drawing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCamera2D_is_margin_drawing_enabled
  = unsafePerformIO $
      withCString "Camera2D" $
        \ clsNamePtr ->
          withCString "is_margin_drawing_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCamera2D_is_margin_drawing_enabled #-}

instance Method "is_margin_drawing_enabled" GodotCamera2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCamera2D_is_margin_drawing_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotJoint2D = GodotJoint2D GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotJoint2D where
        type BaseClass GodotJoint2D = GodotNode2D
        super = coerce
bindJoint2D_set_node_a
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "set_node_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_set_node_a #-}

instance Method "set_node_a" GodotJoint2D (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_set_node_a (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint2D_get_node_a
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "get_node_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_get_node_a #-}

instance Method "get_node_a" GodotJoint2D (IO GodotNodePath) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_get_node_a (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint2D_set_node_b
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "set_node_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_set_node_b #-}

instance Method "set_node_b" GodotJoint2D (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_set_node_b (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint2D_get_node_b
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "get_node_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_get_node_b #-}

instance Method "get_node_b" GodotJoint2D (IO GodotNodePath) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_get_node_b (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint2D_set_bias
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "set_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_set_bias #-}

instance Method "set_bias" GodotJoint2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_set_bias (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint2D_get_bias
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "get_bias" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_get_bias #-}

instance Method "get_bias" GodotJoint2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_get_bias (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint2D_set_exclude_nodes_from_collision
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "set_exclude_nodes_from_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_set_exclude_nodes_from_collision #-}

instance Method "set_exclude_nodes_from_collision" GodotJoint2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_set_exclude_nodes_from_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindJoint2D_get_exclude_nodes_from_collision
  = unsafePerformIO $
      withCString "Joint2D" $
        \ clsNamePtr ->
          withCString "get_exclude_nodes_from_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJoint2D_get_exclude_nodes_from_collision #-}

instance Method "get_exclude_nodes_from_collision" GodotJoint2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJoint2D_get_exclude_nodes_from_collision
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPinJoint2D = GodotPinJoint2D GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotPinJoint2D where
        type BaseClass GodotPinJoint2D = GodotJoint2D
        super = coerce
bindPinJoint2D_set_softness
  = unsafePerformIO $
      withCString "PinJoint2D" $
        \ clsNamePtr ->
          withCString "set_softness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPinJoint2D_set_softness #-}

instance Method "set_softness" GodotPinJoint2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPinJoint2D_set_softness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPinJoint2D_get_softness
  = unsafePerformIO $
      withCString "PinJoint2D" $
        \ clsNamePtr ->
          withCString "get_softness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPinJoint2D_get_softness #-}

instance Method "get_softness" GodotPinJoint2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPinJoint2D_get_softness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGrooveJoint2D = GodotGrooveJoint2D GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotGrooveJoint2D where
        type BaseClass GodotGrooveJoint2D = GodotJoint2D
        super = coerce
bindGrooveJoint2D_set_length
  = unsafePerformIO $
      withCString "GrooveJoint2D" $
        \ clsNamePtr ->
          withCString "set_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGrooveJoint2D_set_length #-}

instance Method "set_length" GodotGrooveJoint2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGrooveJoint2D_set_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGrooveJoint2D_get_length
  = unsafePerformIO $
      withCString "GrooveJoint2D" $
        \ clsNamePtr ->
          withCString "get_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGrooveJoint2D_get_length #-}

instance Method "get_length" GodotGrooveJoint2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGrooveJoint2D_get_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGrooveJoint2D_set_initial_offset
  = unsafePerformIO $
      withCString "GrooveJoint2D" $
        \ clsNamePtr ->
          withCString "set_initial_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGrooveJoint2D_set_initial_offset #-}

instance Method "set_initial_offset" GodotGrooveJoint2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGrooveJoint2D_set_initial_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGrooveJoint2D_get_initial_offset
  = unsafePerformIO $
      withCString "GrooveJoint2D" $
        \ clsNamePtr ->
          withCString "get_initial_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGrooveJoint2D_get_initial_offset #-}

instance Method "get_initial_offset" GodotGrooveJoint2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGrooveJoint2D_get_initial_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotDampedSpringJoint2D = GodotDampedSpringJoint2D GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotDampedSpringJoint2D where
        type BaseClass GodotDampedSpringJoint2D = GodotJoint2D
        super = coerce
bindDampedSpringJoint2D_set_length
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "set_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_set_length #-}

instance Method "set_length" GodotDampedSpringJoint2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_set_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDampedSpringJoint2D_get_length
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "get_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_get_length #-}

instance Method "get_length" GodotDampedSpringJoint2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_get_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDampedSpringJoint2D_set_rest_length
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "set_rest_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_set_rest_length #-}

instance Method "set_rest_length" GodotDampedSpringJoint2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_set_rest_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDampedSpringJoint2D_get_rest_length
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "get_rest_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_get_rest_length #-}

instance Method "get_rest_length" GodotDampedSpringJoint2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_get_rest_length
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDampedSpringJoint2D_set_stiffness
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "set_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_set_stiffness #-}

instance Method "set_stiffness" GodotDampedSpringJoint2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_set_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDampedSpringJoint2D_get_stiffness
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "get_stiffness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_get_stiffness #-}

instance Method "get_stiffness" GodotDampedSpringJoint2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_get_stiffness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDampedSpringJoint2D_set_damping
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "set_damping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_set_damping #-}

instance Method "set_damping" GodotDampedSpringJoint2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_set_damping
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDampedSpringJoint2D_get_damping
  = unsafePerformIO $
      withCString "DampedSpringJoint2D" $
        \ clsNamePtr ->
          withCString "get_damping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDampedSpringJoint2D_get_damping #-}

instance Method "get_damping" GodotDampedSpringJoint2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDampedSpringJoint2D_get_damping
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTileSet = GodotTileSet GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotTileSet where
        type BaseClass GodotTileSet = GodotResource
        super = coerce
bindTileSet__is_tile_bound
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "_is_tile_bound" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet__is_tile_bound #-}

instance Method "_is_tile_bound" GodotTileSet
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet__is_tile_bound (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet__forward_subtile_selection
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "_forward_subtile_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet__forward_subtile_selection #-}

instance Method "_forward_subtile_selection" GodotTileSet
           (Int -> Int -> GodotObject -> GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet__forward_subtile_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_create_tile
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "create_tile" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_create_tile #-}

instance Method "create_tile" GodotTileSet (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_create_tile (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_autotile_set_bitmask_mode
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "autotile_set_bitmask_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_autotile_set_bitmask_mode #-}

instance Method "autotile_set_bitmask_mode" GodotTileSet
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_autotile_set_bitmask_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_autotile_get_bitmask_mode
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "autotile_get_bitmask_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_autotile_get_bitmask_mode #-}

instance Method "autotile_get_bitmask_mode" GodotTileSet
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_autotile_get_bitmask_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_autotile_set_size
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "autotile_set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_autotile_set_size #-}

instance Method "autotile_set_size" GodotTileSet
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_autotile_set_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_autotile_get_size
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "autotile_get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_autotile_get_size #-}

instance Method "autotile_get_size" GodotTileSet
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_autotile_get_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_name
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_name #-}

instance Method "tile_set_name" GodotTileSet
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_name
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_name #-}

instance Method "tile_get_name" GodotTileSet
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_texture
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_texture #-}

instance Method "tile_set_texture" GodotTileSet
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_texture
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_texture #-}

instance Method "tile_get_texture" GodotTileSet
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_normal_map
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_normal_map #-}

instance Method "tile_set_normal_map" GodotTileSet
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_normal_map (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_normal_map
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_normal_map #-}

instance Method "tile_get_normal_map" GodotTileSet
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_normal_map (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_material
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_material #-}

instance Method "tile_set_material" GodotTileSet
           (Int -> GodotShaderMaterial -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_material
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_material #-}

instance Method "tile_get_material" GodotTileSet
           (Int -> IO GodotShaderMaterial)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_modulate
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_modulate #-}

instance Method "tile_set_modulate" GodotTileSet
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_modulate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_modulate
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_modulate #-}

instance Method "tile_get_modulate" GodotTileSet
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_modulate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_texture_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_texture_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_texture_offset #-}

instance Method "tile_set_texture_offset" GodotTileSet
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_texture_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_texture_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_texture_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_texture_offset #-}

instance Method "tile_get_texture_offset" GodotTileSet
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_texture_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_region
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_region #-}

instance Method "tile_set_region" GodotTileSet
           (Int -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_region
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_region #-}

instance Method "tile_get_region" GodotTileSet
           (Int -> IO GodotRect2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_shape
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_shape #-}

instance Method "tile_set_shape" GodotTileSet
           (Int -> Int -> GodotShape2D -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_shape
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_shape #-}

instance Method "tile_get_shape" GodotTileSet
           (Int -> Int -> IO GodotShape2D)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_shape_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_shape_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_shape_offset #-}

instance Method "tile_set_shape_offset" GodotTileSet
           (Int -> Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_shape_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_shape_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_shape_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_shape_offset #-}

instance Method "tile_get_shape_offset" GodotTileSet
           (Int -> Int -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_shape_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_shape_transform
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_shape_transform #-}

instance Method "tile_set_shape_transform" GodotTileSet
           (Int -> Int -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_shape_transform
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_shape_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_shape_transform #-}

instance Method "tile_get_shape_transform" GodotTileSet
           (Int -> Int -> IO GodotTransform2d)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_shape_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_shape_one_way
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_shape_one_way" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_shape_one_way #-}

instance Method "tile_set_shape_one_way" GodotTileSet
           (Int -> Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_shape_one_way
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_shape_one_way
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_shape_one_way" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_shape_one_way #-}

instance Method "tile_get_shape_one_way" GodotTileSet
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_shape_one_way
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_add_shape
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_add_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_add_shape #-}

instance Method "tile_add_shape" GodotTileSet
           (Int ->
              GodotShape2D -> GodotTransform2d -> Bool -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_add_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_shape_count
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_shape_count #-}

instance Method "tile_get_shape_count" GodotTileSet (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_shapes
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_shapes #-}

instance Method "tile_set_shapes" GodotTileSet
           (Int -> GodotArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_shapes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_shapes
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_shapes #-}

instance Method "tile_get_shapes" GodotTileSet
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_shapes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_tile_mode
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_tile_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_tile_mode #-}

instance Method "tile_set_tile_mode" GodotTileSet
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_tile_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_tile_mode
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_tile_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_tile_mode #-}

instance Method "tile_get_tile_mode" GodotTileSet (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_tile_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_navigation_polygon
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_navigation_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_navigation_polygon #-}

instance Method "tile_set_navigation_polygon" GodotTileSet
           (Int -> GodotNavigationPolygon -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_navigation_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_navigation_polygon
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_navigation_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_navigation_polygon #-}

instance Method "tile_get_navigation_polygon" GodotTileSet
           (Int -> IO GodotNavigationPolygon)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_navigation_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_navigation_polygon_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_navigation_polygon_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_navigation_polygon_offset #-}

instance Method "tile_set_navigation_polygon_offset" GodotTileSet
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTileSet_tile_set_navigation_polygon_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_navigation_polygon_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_navigation_polygon_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_navigation_polygon_offset #-}

instance Method "tile_get_navigation_polygon_offset" GodotTileSet
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTileSet_tile_get_navigation_polygon_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_light_occluder
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_light_occluder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_light_occluder #-}

instance Method "tile_set_light_occluder" GodotTileSet
           (Int -> GodotOccluderPolygon2D -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_light_occluder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_light_occluder
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_light_occluder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_light_occluder #-}

instance Method "tile_get_light_occluder" GodotTileSet
           (Int -> IO GodotOccluderPolygon2D)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_light_occluder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_occluder_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_occluder_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_occluder_offset #-}

instance Method "tile_set_occluder_offset" GodotTileSet
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_occluder_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_occluder_offset
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_occluder_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_occluder_offset #-}

instance Method "tile_get_occluder_offset" GodotTileSet
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_occluder_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_set_z_index
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_set_z_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_set_z_index #-}

instance Method "tile_set_z_index" GodotTileSet
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_set_z_index (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_tile_get_z_index
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "tile_get_z_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_tile_get_z_index #-}

instance Method "tile_get_z_index" GodotTileSet (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_tile_get_z_index (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_remove_tile
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "remove_tile" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_remove_tile #-}

instance Method "remove_tile" GodotTileSet (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_remove_tile (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_clear
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_clear #-}

instance Method "clear" GodotTileSet (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_get_last_unused_tile_id
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "get_last_unused_tile_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_get_last_unused_tile_id #-}

instance Method "get_last_unused_tile_id" GodotTileSet (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_get_last_unused_tile_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_find_tile_by_name
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "find_tile_by_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_find_tile_by_name #-}

instance Method "find_tile_by_name" GodotTileSet
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_find_tile_by_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileSet_get_tiles_ids
  = unsafePerformIO $
      withCString "TileSet" $
        \ clsNamePtr ->
          withCString "get_tiles_ids" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileSet_get_tiles_ids #-}

instance Method "get_tiles_ids" GodotTileSet (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileSet_get_tiles_ids (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTileMap = GodotTileMap GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotTileMap where
        type BaseClass GodotTileMap = GodotNode2D
        super = coerce
bindTileMap_set_tileset
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_tileset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_tileset #-}

instance Method "set_tileset" GodotTileMap (GodotTileSet -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_tileset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_tileset
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_tileset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_tileset #-}

instance Method "get_tileset" GodotTileMap (IO GodotTileSet) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_tileset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_mode
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_mode #-}

instance Method "set_mode" GodotTileMap (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_mode (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_mode
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_mode #-}

instance Method "get_mode" GodotTileMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_mode (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_half_offset
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_half_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_half_offset #-}

instance Method "set_half_offset" GodotTileMap (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_half_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_half_offset
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_half_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_half_offset #-}

instance Method "get_half_offset" GodotTileMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_half_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_custom_transform
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_custom_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_custom_transform #-}

instance Method "set_custom_transform" GodotTileMap
           (GodotTransform2d -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_custom_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_custom_transform
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_custom_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_custom_transform #-}

instance Method "get_custom_transform" GodotTileMap
           (IO GodotTransform2d)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_custom_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_cell_size
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_cell_size #-}

instance Method "set_cell_size" GodotTileMap
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_cell_size
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_cell_size #-}

instance Method "get_cell_size" GodotTileMap (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap__set_old_cell_size
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "_set_old_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap__set_old_cell_size #-}

instance Method "_set_old_cell_size" GodotTileMap (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap__set_old_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap__get_old_cell_size
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "_get_old_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap__get_old_cell_size #-}

instance Method "_get_old_cell_size" GodotTileMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap__get_old_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_quadrant_size
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_quadrant_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_quadrant_size #-}

instance Method "set_quadrant_size" GodotTileMap (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_quadrant_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_quadrant_size
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_quadrant_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_quadrant_size #-}

instance Method "get_quadrant_size" GodotTileMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_quadrant_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_tile_origin
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_tile_origin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_tile_origin #-}

instance Method "set_tile_origin" GodotTileMap (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_tile_origin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_tile_origin
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_tile_origin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_tile_origin #-}

instance Method "get_tile_origin" GodotTileMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_tile_origin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_clip_uv
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_clip_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_clip_uv #-}

instance Method "set_clip_uv" GodotTileMap (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_clip_uv (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_clip_uv
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_clip_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_clip_uv #-}

instance Method "get_clip_uv" GodotTileMap (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_clip_uv (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_y_sort_mode
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_y_sort_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_y_sort_mode #-}

instance Method "set_y_sort_mode" GodotTileMap (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_y_sort_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_is_y_sort_mode_enabled
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "is_y_sort_mode_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_is_y_sort_mode_enabled #-}

instance Method "is_y_sort_mode_enabled" GodotTileMap (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_is_y_sort_mode_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_collision_use_kinematic
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_collision_use_kinematic" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_collision_use_kinematic #-}

instance Method "set_collision_use_kinematic" GodotTileMap
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_collision_use_kinematic
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_collision_use_kinematic
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_collision_use_kinematic" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_collision_use_kinematic #-}

instance Method "get_collision_use_kinematic" GodotTileMap
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_collision_use_kinematic
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_collision_layer
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_collision_layer #-}

instance Method "set_collision_layer" GodotTileMap (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_collision_layer
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_collision_layer #-}

instance Method "get_collision_layer" GodotTileMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_collision_mask
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_collision_mask #-}

instance Method "set_collision_mask" GodotTileMap (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_collision_mask
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_collision_mask #-}

instance Method "get_collision_mask" GodotTileMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_collision_layer_bit
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_collision_layer_bit #-}

instance Method "set_collision_layer_bit" GodotTileMap
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_collision_layer_bit
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_collision_layer_bit #-}

instance Method "get_collision_layer_bit" GodotTileMap
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_collision_mask_bit
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotTileMap
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_collision_mask_bit
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotTileMap
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_collision_friction
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_collision_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_collision_friction #-}

instance Method "set_collision_friction" GodotTileMap
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_collision_friction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_collision_friction
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_collision_friction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_collision_friction #-}

instance Method "get_collision_friction" GodotTileMap (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_collision_friction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_collision_bounce
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_collision_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_collision_bounce #-}

instance Method "set_collision_bounce" GodotTileMap
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_collision_bounce
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_collision_bounce
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_collision_bounce" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_collision_bounce #-}

instance Method "get_collision_bounce" GodotTileMap (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_collision_bounce
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_occluder_light_mask
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_occluder_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_occluder_light_mask #-}

instance Method "set_occluder_light_mask" GodotTileMap
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_occluder_light_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_occluder_light_mask
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_occluder_light_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_occluder_light_mask #-}

instance Method "get_occluder_light_mask" GodotTileMap (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_occluder_light_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_cell
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_cell" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_cell #-}

instance Method "set_cell" GodotTileMap
           (Int ->
              Int -> Int -> Bool -> Bool -> Bool -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6 arg7
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6, toVariant arg7]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_cell (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_set_cellv
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "set_cellv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_set_cellv #-}

instance Method "set_cellv" GodotTileMap
           (GodotVector2 -> Int -> Bool -> Bool -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_set_cellv (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap__set_celld
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "_set_celld" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap__set_celld #-}

instance Method "_set_celld" GodotTileMap
           (GodotVector2 -> GodotDictionary -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap__set_celld (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_cell
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_cell" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_cell #-}

instance Method "get_cell" GodotTileMap (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_cell (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_cellv
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_cellv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_cellv #-}

instance Method "get_cellv" GodotTileMap (GodotVector2 -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_cellv (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_is_cell_x_flipped
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "is_cell_x_flipped" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_is_cell_x_flipped #-}

instance Method "is_cell_x_flipped" GodotTileMap
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_is_cell_x_flipped (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_is_cell_y_flipped
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "is_cell_y_flipped" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_is_cell_y_flipped #-}

instance Method "is_cell_y_flipped" GodotTileMap
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_is_cell_y_flipped (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_is_cell_transposed
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "is_cell_transposed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_is_cell_transposed #-}

instance Method "is_cell_transposed" GodotTileMap
           (Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_is_cell_transposed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_fix_invalid_tiles
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "fix_invalid_tiles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_fix_invalid_tiles #-}

instance Method "fix_invalid_tiles" GodotTileMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_fix_invalid_tiles (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_clear
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_clear #-}

instance Method "clear" GodotTileMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_used_cells
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_used_cells" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_used_cells #-}

instance Method "get_used_cells" GodotTileMap (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_used_cells (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_used_cells_by_id
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_used_cells_by_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_used_cells_by_id #-}

instance Method "get_used_cells_by_id" GodotTileMap
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_used_cells_by_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_get_used_rect
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "get_used_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_get_used_rect #-}

instance Method "get_used_rect" GodotTileMap (IO GodotRect2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_get_used_rect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_map_to_world
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "map_to_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_map_to_world #-}

instance Method "map_to_world" GodotTileMap
           (GodotVector2 -> Bool -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_map_to_world (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_world_to_map
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "world_to_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_world_to_map #-}

instance Method "world_to_map" GodotTileMap
           (GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_world_to_map (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap__clear_quadrants
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "_clear_quadrants" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap__clear_quadrants #-}

instance Method "_clear_quadrants" GodotTileMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap__clear_quadrants (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap__recreate_quadrants
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "_recreate_quadrants" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap__recreate_quadrants #-}

instance Method "_recreate_quadrants" GodotTileMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap__recreate_quadrants (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_update_dirty_quadrants
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "update_dirty_quadrants" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_update_dirty_quadrants #-}

instance Method "update_dirty_quadrants" GodotTileMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_update_dirty_quadrants
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_update_bitmask_area
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "update_bitmask_area" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_update_bitmask_area #-}

instance Method "update_bitmask_area" GodotTileMap
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_update_bitmask_area (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap_update_bitmask_region
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "update_bitmask_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap_update_bitmask_region #-}

instance Method "update_bitmask_region" GodotTileMap
           (GodotVector2 -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap_update_bitmask_region
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap__set_tile_data
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "_set_tile_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap__set_tile_data #-}

instance Method "_set_tile_data" GodotTileMap
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap__set_tile_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTileMap__get_tile_data
  = unsafePerformIO $
      withCString "TileMap" $
        \ clsNamePtr ->
          withCString "_get_tile_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTileMap__get_tile_data #-}

instance Method "_get_tile_data" GodotTileMap
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTileMap__get_tile_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotParallaxBackground = GodotParallaxBackground GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotParallaxBackground where
        type BaseClass GodotParallaxBackground = GodotCanvasLayer
        super = coerce
bindParallaxBackground__camera_moved
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "_camera_moved" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground__camera_moved #-}

instance Method "_camera_moved" GodotParallaxBackground
           (GodotTransform2d -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground__camera_moved
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_set_scroll_offset
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "set_scroll_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_set_scroll_offset #-}

instance Method "set_scroll_offset" GodotParallaxBackground
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_set_scroll_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_get_scroll_offset
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "get_scroll_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_get_scroll_offset #-}

instance Method "get_scroll_offset" GodotParallaxBackground
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_get_scroll_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_set_scroll_base_offset
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "set_scroll_base_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_set_scroll_base_offset #-}

instance Method "set_scroll_base_offset" GodotParallaxBackground
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParallaxBackground_set_scroll_base_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_get_scroll_base_offset
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "get_scroll_base_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_get_scroll_base_offset #-}

instance Method "get_scroll_base_offset" GodotParallaxBackground
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParallaxBackground_get_scroll_base_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_set_scroll_base_scale
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "set_scroll_base_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_set_scroll_base_scale #-}

instance Method "set_scroll_base_scale" GodotParallaxBackground
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_set_scroll_base_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_get_scroll_base_scale
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "get_scroll_base_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_get_scroll_base_scale #-}

instance Method "get_scroll_base_scale" GodotParallaxBackground
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_get_scroll_base_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_set_limit_begin
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "set_limit_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_set_limit_begin #-}

instance Method "set_limit_begin" GodotParallaxBackground
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_set_limit_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_get_limit_begin
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "get_limit_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_get_limit_begin #-}

instance Method "get_limit_begin" GodotParallaxBackground
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_get_limit_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_set_limit_end
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "set_limit_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_set_limit_end #-}

instance Method "set_limit_end" GodotParallaxBackground
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_set_limit_end
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_get_limit_end
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "get_limit_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_get_limit_end #-}

instance Method "get_limit_end" GodotParallaxBackground
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_get_limit_end
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_set_ignore_camera_zoom
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "set_ignore_camera_zoom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_set_ignore_camera_zoom #-}

instance Method "set_ignore_camera_zoom" GodotParallaxBackground
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParallaxBackground_set_ignore_camera_zoom
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxBackground_is_ignore_camera_zoom
  = unsafePerformIO $
      withCString "ParallaxBackground" $
        \ clsNamePtr ->
          withCString "is_ignore_camera_zoom" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxBackground_is_ignore_camera_zoom #-}

instance Method "is_ignore_camera_zoom" GodotParallaxBackground
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxBackground_is_ignore_camera_zoom
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotParallaxLayer = GodotParallaxLayer GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotParallaxLayer where
        type BaseClass GodotParallaxLayer = GodotNode2D
        super = coerce
bindParallaxLayer_set_motion_scale
  = unsafePerformIO $
      withCString "ParallaxLayer" $
        \ clsNamePtr ->
          withCString "set_motion_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxLayer_set_motion_scale #-}

instance Method "set_motion_scale" GodotParallaxLayer
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxLayer_set_motion_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxLayer_get_motion_scale
  = unsafePerformIO $
      withCString "ParallaxLayer" $
        \ clsNamePtr ->
          withCString "get_motion_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxLayer_get_motion_scale #-}

instance Method "get_motion_scale" GodotParallaxLayer
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxLayer_get_motion_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxLayer_set_motion_offset
  = unsafePerformIO $
      withCString "ParallaxLayer" $
        \ clsNamePtr ->
          withCString "set_motion_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxLayer_set_motion_offset #-}

instance Method "set_motion_offset" GodotParallaxLayer
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxLayer_set_motion_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxLayer_get_motion_offset
  = unsafePerformIO $
      withCString "ParallaxLayer" $
        \ clsNamePtr ->
          withCString "get_motion_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxLayer_get_motion_offset #-}

instance Method "get_motion_offset" GodotParallaxLayer
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxLayer_get_motion_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxLayer_set_mirroring
  = unsafePerformIO $
      withCString "ParallaxLayer" $
        \ clsNamePtr ->
          withCString "set_mirroring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxLayer_set_mirroring #-}

instance Method "set_mirroring" GodotParallaxLayer
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxLayer_set_mirroring (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParallaxLayer_get_mirroring
  = unsafePerformIO $
      withCString "ParallaxLayer" $
        \ clsNamePtr ->
          withCString "get_mirroring" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParallaxLayer_get_mirroring #-}

instance Method "get_mirroring" GodotParallaxLayer
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParallaxLayer_get_mirroring (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTouchScreenButton = GodotTouchScreenButton GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotTouchScreenButton where
        type BaseClass GodotTouchScreenButton = GodotNode2D
        super = coerce
bindTouchScreenButton_set_texture
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_texture #-}

instance Method "set_texture" GodotTouchScreenButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_get_texture
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_get_texture #-}

instance Method "get_texture" GodotTouchScreenButton
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_get_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_texture_pressed
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_texture_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_texture_pressed #-}

instance Method "set_texture_pressed" GodotTouchScreenButton
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_texture_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_get_texture_pressed
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "get_texture_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_get_texture_pressed #-}

instance Method "get_texture_pressed" GodotTouchScreenButton
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_get_texture_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_bitmask
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_bitmask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_bitmask #-}

instance Method "set_bitmask" GodotTouchScreenButton
           (GodotBitMap -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_bitmask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_get_bitmask
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "get_bitmask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_get_bitmask #-}

instance Method "get_bitmask" GodotTouchScreenButton
           (IO GodotBitMap)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_get_bitmask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_shape
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_shape #-}

instance Method "set_shape" GodotTouchScreenButton
           (GodotShape2D -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_get_shape
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "get_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_get_shape #-}

instance Method "get_shape" GodotTouchScreenButton
           (IO GodotShape2D)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_get_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_shape_centered
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_shape_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_shape_centered #-}

instance Method "set_shape_centered" GodotTouchScreenButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_shape_centered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_is_shape_centered
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "is_shape_centered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_is_shape_centered #-}

instance Method "is_shape_centered" GodotTouchScreenButton
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_is_shape_centered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_shape_visible
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_shape_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_shape_visible #-}

instance Method "set_shape_visible" GodotTouchScreenButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_shape_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_is_shape_visible
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "is_shape_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_is_shape_visible #-}

instance Method "is_shape_visible" GodotTouchScreenButton (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_is_shape_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_action
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_action #-}

instance Method "set_action" GodotTouchScreenButton
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_action
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_get_action
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "get_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_get_action #-}

instance Method "get_action" GodotTouchScreenButton
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_get_action
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_visibility_mode
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_visibility_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_visibility_mode #-}

instance Method "set_visibility_mode" GodotTouchScreenButton
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_visibility_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_get_visibility_mode
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "get_visibility_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_get_visibility_mode #-}

instance Method "get_visibility_mode" GodotTouchScreenButton
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_get_visibility_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_set_passby_press
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "set_passby_press" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_set_passby_press #-}

instance Method "set_passby_press" GodotTouchScreenButton
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_set_passby_press
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_is_passby_press_enabled
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "is_passby_press_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_is_passby_press_enabled #-}

instance Method "is_passby_press_enabled" GodotTouchScreenButton
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindTouchScreenButton_is_passby_press_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton_is_pressed
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "is_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton_is_pressed #-}

instance Method "is_pressed" GodotTouchScreenButton (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton_is_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTouchScreenButton__input
  = unsafePerformIO $
      withCString "TouchScreenButton" $
        \ clsNamePtr ->
          withCString "_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTouchScreenButton__input #-}

instance Method "_input" GodotTouchScreenButton
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTouchScreenButton__input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRemoteTransform2D = GodotRemoteTransform2D GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotRemoteTransform2D where
        type BaseClass GodotRemoteTransform2D = GodotNode2D
        super = coerce
bindRemoteTransform2D_set_remote_node
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "set_remote_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_set_remote_node #-}

instance Method "set_remote_node" GodotRemoteTransform2D
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_set_remote_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_get_remote_node
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "get_remote_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_get_remote_node #-}

instance Method "get_remote_node" GodotRemoteTransform2D
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_get_remote_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_set_use_global_coordinates
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "set_use_global_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_set_use_global_coordinates #-}

instance Method "set_use_global_coordinates" GodotRemoteTransform2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRemoteTransform2D_set_use_global_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_get_use_global_coordinates
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "get_use_global_coordinates" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_get_use_global_coordinates #-}

instance Method "get_use_global_coordinates" GodotRemoteTransform2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindRemoteTransform2D_get_use_global_coordinates
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_set_update_position
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "set_update_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_set_update_position #-}

instance Method "set_update_position" GodotRemoteTransform2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_set_update_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_get_update_position
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "get_update_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_get_update_position #-}

instance Method "get_update_position" GodotRemoteTransform2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_get_update_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_set_update_rotation
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "set_update_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_set_update_rotation #-}

instance Method "set_update_rotation" GodotRemoteTransform2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_set_update_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_get_update_rotation
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "get_update_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_get_update_rotation #-}

instance Method "get_update_rotation" GodotRemoteTransform2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_get_update_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_set_update_scale
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "set_update_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_set_update_scale #-}

instance Method "set_update_scale" GodotRemoteTransform2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_set_update_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRemoteTransform2D_get_update_scale
  = unsafePerformIO $
      withCString "RemoteTransform2D" $
        \ clsNamePtr ->
          withCString "get_update_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRemoteTransform2D_get_update_scale #-}

instance Method "get_update_scale" GodotRemoteTransform2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRemoteTransform2D_get_update_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotParticlesMaterial = GodotParticlesMaterial GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotParticlesMaterial where
        type BaseClass GodotParticlesMaterial = GodotMaterial
        super = coerce
bindParticlesMaterial_set_spread
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_spread #-}

instance Method "set_spread" GodotParticlesMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_spread
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_spread
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_spread" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_spread #-}

instance Method "get_spread" GodotParticlesMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_spread
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_flatness
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_flatness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_flatness #-}

instance Method "set_flatness" GodotParticlesMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_flatness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_flatness
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_flatness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_flatness #-}

instance Method "get_flatness" GodotParticlesMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_flatness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_param
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_param #-}

instance Method "set_param" GodotParticlesMaterial
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_param
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_param" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_param #-}

instance Method "get_param" GodotParticlesMaterial
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_param (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_param_randomness
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_param_randomness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_param_randomness #-}

instance Method "set_param_randomness" GodotParticlesMaterial
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_param_randomness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_param_randomness
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_param_randomness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_param_randomness #-}

instance Method "get_param_randomness" GodotParticlesMaterial
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_param_randomness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_param_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_param_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_param_texture #-}

instance Method "set_param_texture" GodotParticlesMaterial
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_param_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_param_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_param_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_param_texture #-}

instance Method "get_param_texture" GodotParticlesMaterial
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_param_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_color
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_color #-}

instance Method "set_color" GodotParticlesMaterial
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_color
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_color #-}

instance Method "get_color" GodotParticlesMaterial (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_color_ramp
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_color_ramp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_color_ramp #-}

instance Method "set_color_ramp" GodotParticlesMaterial
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_color_ramp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_color_ramp
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_color_ramp" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_color_ramp #-}

instance Method "get_color_ramp" GodotParticlesMaterial
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_color_ramp
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_flag
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_flag #-}

instance Method "set_flag" GodotParticlesMaterial
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_flag
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_flag #-}

instance Method "get_flag" GodotParticlesMaterial (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_emission_shape
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_emission_shape #-}

instance Method "set_emission_shape" GodotParticlesMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_emission_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_emission_shape
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_emission_shape #-}

instance Method "get_emission_shape" GodotParticlesMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_emission_shape
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_emission_sphere_radius
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_sphere_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_emission_sphere_radius #-}

instance Method "set_emission_sphere_radius" GodotParticlesMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_emission_sphere_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_emission_sphere_radius
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_sphere_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_emission_sphere_radius #-}

instance Method "get_emission_sphere_radius" GodotParticlesMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_emission_sphere_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_emission_box_extents
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_box_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_emission_box_extents #-}

instance Method "set_emission_box_extents" GodotParticlesMaterial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_emission_box_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_emission_box_extents
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_box_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_emission_box_extents #-}

instance Method "get_emission_box_extents" GodotParticlesMaterial
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_emission_box_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_emission_point_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_point_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_emission_point_texture #-}

instance Method "set_emission_point_texture" GodotParticlesMaterial
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_emission_point_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_emission_point_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_point_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_emission_point_texture #-}

instance Method "get_emission_point_texture" GodotParticlesMaterial
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_emission_point_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_emission_normal_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_normal_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_emission_normal_texture #-}

instance Method "set_emission_normal_texture"
           GodotParticlesMaterial
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_emission_normal_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_emission_normal_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_normal_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_emission_normal_texture #-}

instance Method "get_emission_normal_texture"
           GodotParticlesMaterial
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_emission_normal_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_emission_color_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_color_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_emission_color_texture #-}

instance Method "set_emission_color_texture" GodotParticlesMaterial
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_emission_color_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_emission_color_texture
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_color_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_emission_color_texture #-}

instance Method "get_emission_color_texture" GodotParticlesMaterial
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_emission_color_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_emission_point_count
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_emission_point_count #-}

instance Method "set_emission_point_count" GodotParticlesMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_emission_point_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_emission_point_count
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_emission_point_count #-}

instance Method "get_emission_point_count" GodotParticlesMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_emission_point_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_trail_divisor
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_trail_divisor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_trail_divisor #-}

instance Method "set_trail_divisor" GodotParticlesMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_trail_divisor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_trail_divisor
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_trail_divisor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_trail_divisor #-}

instance Method "get_trail_divisor" GodotParticlesMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_trail_divisor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_trail_size_modifier
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_trail_size_modifier" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_trail_size_modifier #-}

instance Method "set_trail_size_modifier" GodotParticlesMaterial
           (GodotCurveTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_trail_size_modifier
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_trail_size_modifier
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_trail_size_modifier" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_trail_size_modifier #-}

instance Method "get_trail_size_modifier" GodotParticlesMaterial
           (IO GodotCurveTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_trail_size_modifier
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_trail_color_modifier
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_trail_color_modifier" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_trail_color_modifier #-}

instance Method "set_trail_color_modifier" GodotParticlesMaterial
           (GodotGradientTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_set_trail_color_modifier
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_trail_color_modifier
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_trail_color_modifier" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_trail_color_modifier #-}

instance Method "get_trail_color_modifier" GodotParticlesMaterial
           (IO GodotGradientTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindParticlesMaterial_get_trail_color_modifier
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_get_gravity
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "get_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_get_gravity #-}

instance Method "get_gravity" GodotParticlesMaterial
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_get_gravity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindParticlesMaterial_set_gravity
  = unsafePerformIO $
      withCString "ParticlesMaterial" $
        \ clsNamePtr ->
          withCString "set_gravity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindParticlesMaterial_set_gravity #-}

instance Method "set_gravity" GodotParticlesMaterial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindParticlesMaterial_set_gravity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCurveTexture = GodotCurveTexture GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotCurveTexture where
        type BaseClass GodotCurveTexture = GodotTexture
        super = coerce
bindCurveTexture_get_width
  = unsafePerformIO $
      withCString "CurveTexture" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurveTexture_get_width #-}

instance Method "get_width" GodotCurveTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurveTexture_get_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurveTexture_set_width
  = unsafePerformIO $
      withCString "CurveTexture" $
        \ clsNamePtr ->
          withCString "set_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurveTexture_set_width #-}

instance Method "set_width" GodotCurveTexture (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurveTexture_set_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurveTexture_set_curve
  = unsafePerformIO $
      withCString "CurveTexture" $
        \ clsNamePtr ->
          withCString "set_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurveTexture_set_curve #-}

instance Method "set_curve" GodotCurveTexture (GodotCurve -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurveTexture_set_curve (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurveTexture_get_curve
  = unsafePerformIO $
      withCString "CurveTexture" $
        \ clsNamePtr ->
          withCString "get_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurveTexture_get_curve #-}

instance Method "get_curve" GodotCurveTexture (IO GodotCurve) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurveTexture_get_curve (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurveTexture__update
  = unsafePerformIO $
      withCString "CurveTexture" $
        \ clsNamePtr ->
          withCString "_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurveTexture__update #-}

instance Method "_update" GodotCurveTexture (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurveTexture__update (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotArrayMesh = GodotArrayMesh GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotArrayMesh where
        type BaseClass GodotArrayMesh = GodotMesh
        super = coerce
bindArrayMesh_add_blend_shape
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "add_blend_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_add_blend_shape #-}

instance Method "add_blend_shape" GodotArrayMesh
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_add_blend_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_get_blend_shape_count
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "get_blend_shape_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_get_blend_shape_count #-}

instance Method "get_blend_shape_count" GodotArrayMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_get_blend_shape_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_get_blend_shape_name
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "get_blend_shape_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_get_blend_shape_name #-}

instance Method "get_blend_shape_name" GodotArrayMesh
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_get_blend_shape_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_clear_blend_shapes
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "clear_blend_shapes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_clear_blend_shapes #-}

instance Method "clear_blend_shapes" GodotArrayMesh (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_clear_blend_shapes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_set_blend_shape_mode
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "set_blend_shape_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_set_blend_shape_mode #-}

instance Method "set_blend_shape_mode" GodotArrayMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_set_blend_shape_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_get_blend_shape_mode
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "get_blend_shape_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_get_blend_shape_mode #-}

instance Method "get_blend_shape_mode" GodotArrayMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_get_blend_shape_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_add_surface_from_arrays
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "add_surface_from_arrays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_add_surface_from_arrays #-}

instance Method "add_surface_from_arrays" GodotArrayMesh
           (Int -> GodotArray -> GodotArray -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_add_surface_from_arrays
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_remove
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_remove" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_remove #-}

instance Method "surface_remove" GodotArrayMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_remove (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_update_region
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_update_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_update_region #-}

instance Method "surface_update_region" GodotArrayMesh
           (Int -> Int -> GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_update_region
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_get_array_len
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_get_array_len" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_get_array_len #-}

instance Method "surface_get_array_len" GodotArrayMesh
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_get_array_len
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_get_array_index_len
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_get_array_index_len" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_get_array_index_len #-}

instance Method "surface_get_array_index_len" GodotArrayMesh
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_get_array_index_len
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_get_format
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_get_format #-}

instance Method "surface_get_format" GodotArrayMesh (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_get_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_get_primitive_type
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_get_primitive_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_get_primitive_type #-}

instance Method "surface_get_primitive_type" GodotArrayMesh
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_get_primitive_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_set_material
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_set_material #-}

instance Method "surface_set_material" GodotArrayMesh
           (Int -> GodotMaterial -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_set_material
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_find_by_name
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_find_by_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_find_by_name #-}

instance Method "surface_find_by_name" GodotArrayMesh
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_find_by_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_set_name
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_set_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_set_name #-}

instance Method "surface_set_name" GodotArrayMesh
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_set_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_surface_get_name
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "surface_get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_surface_get_name #-}

instance Method "surface_get_name" GodotArrayMesh
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_surface_get_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_center_geometry
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "center_geometry" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_center_geometry #-}

instance Method "center_geometry" GodotArrayMesh (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_center_geometry (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_regen_normalmaps
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "regen_normalmaps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_regen_normalmaps #-}

instance Method "regen_normalmaps" GodotArrayMesh (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_regen_normalmaps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_lightmap_unwrap
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "lightmap_unwrap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_lightmap_unwrap #-}

instance Method "lightmap_unwrap" GodotArrayMesh
           (GodotTransform -> Float -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_lightmap_unwrap (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_set_custom_aabb
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "set_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_set_custom_aabb #-}

instance Method "set_custom_aabb" GodotArrayMesh
           (GodotAabb -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_set_custom_aabb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindArrayMesh_get_custom_aabb
  = unsafePerformIO $
      withCString "ArrayMesh" $
        \ clsNamePtr ->
          withCString "get_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindArrayMesh_get_custom_aabb #-}

instance Method "get_custom_aabb" GodotArrayMesh (IO GodotAabb)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindArrayMesh_get_custom_aabb (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPrimitiveMesh = GodotPrimitiveMesh GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotPrimitiveMesh where
        type BaseClass GodotPrimitiveMesh = GodotMesh
        super = coerce
bindPrimitiveMesh__update
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "_update" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh__update #-}

instance Method "_update" GodotPrimitiveMesh (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh__update (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrimitiveMesh_set_material
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh_set_material #-}

instance Method "set_material" GodotPrimitiveMesh
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrimitiveMesh_get_material
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh_get_material #-}

instance Method "get_material" GodotPrimitiveMesh
           (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrimitiveMesh_get_mesh_arrays
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "get_mesh_arrays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh_get_mesh_arrays #-}

instance Method "get_mesh_arrays" GodotPrimitiveMesh
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh_get_mesh_arrays
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrimitiveMesh_set_custom_aabb
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "set_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh_set_custom_aabb #-}

instance Method "set_custom_aabb" GodotPrimitiveMesh
           (GodotAabb -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh_set_custom_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrimitiveMesh_get_custom_aabb
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "get_custom_aabb" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh_get_custom_aabb #-}

instance Method "get_custom_aabb" GodotPrimitiveMesh (IO GodotAabb)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh_get_custom_aabb
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrimitiveMesh_set_flip_faces
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "set_flip_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh_set_flip_faces #-}

instance Method "set_flip_faces" GodotPrimitiveMesh (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh_set_flip_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrimitiveMesh_get_flip_faces
  = unsafePerformIO $
      withCString "PrimitiveMesh" $
        \ clsNamePtr ->
          withCString "get_flip_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrimitiveMesh_get_flip_faces #-}

instance Method "get_flip_faces" GodotPrimitiveMesh (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrimitiveMesh_get_flip_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCapsuleMesh = GodotCapsuleMesh GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotCapsuleMesh where
        type BaseClass GodotCapsuleMesh = GodotPrimitiveMesh
        super = coerce
bindCapsuleMesh_set_radius
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_set_radius #-}

instance Method "set_radius" GodotCapsuleMesh (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleMesh_get_radius
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_get_radius #-}

instance Method "get_radius" GodotCapsuleMesh (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleMesh_set_mid_height
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "set_mid_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_set_mid_height #-}

instance Method "set_mid_height" GodotCapsuleMesh (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_set_mid_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleMesh_get_mid_height
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "get_mid_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_get_mid_height #-}

instance Method "get_mid_height" GodotCapsuleMesh (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_get_mid_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleMesh_set_radial_segments
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "set_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_set_radial_segments #-}

instance Method "set_radial_segments" GodotCapsuleMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_set_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleMesh_get_radial_segments
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "get_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_get_radial_segments #-}

instance Method "get_radial_segments" GodotCapsuleMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_get_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleMesh_set_rings
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "set_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_set_rings #-}

instance Method "set_rings" GodotCapsuleMesh (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_set_rings (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleMesh_get_rings
  = unsafePerformIO $
      withCString "CapsuleMesh" $
        \ clsNamePtr ->
          withCString "get_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleMesh_get_rings #-}

instance Method "get_rings" GodotCapsuleMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleMesh_get_rings (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCubeMesh = GodotCubeMesh GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotCubeMesh where
        type BaseClass GodotCubeMesh = GodotPrimitiveMesh
        super = coerce
bindCubeMesh_set_size
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_set_size #-}

instance Method "set_size" GodotCubeMesh (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_set_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMesh_get_size
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_get_size #-}

instance Method "get_size" GodotCubeMesh (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_get_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMesh_set_subdivide_width
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_set_subdivide_width #-}

instance Method "set_subdivide_width" GodotCubeMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_set_subdivide_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMesh_get_subdivide_width
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_get_subdivide_width #-}

instance Method "get_subdivide_width" GodotCubeMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_get_subdivide_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMesh_set_subdivide_height
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_set_subdivide_height #-}

instance Method "set_subdivide_height" GodotCubeMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_set_subdivide_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMesh_get_subdivide_height
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_get_subdivide_height #-}

instance Method "get_subdivide_height" GodotCubeMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_get_subdivide_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMesh_set_subdivide_depth
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_set_subdivide_depth #-}

instance Method "set_subdivide_depth" GodotCubeMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_set_subdivide_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCubeMesh_get_subdivide_depth
  = unsafePerformIO $
      withCString "CubeMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCubeMesh_get_subdivide_depth #-}

instance Method "get_subdivide_depth" GodotCubeMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCubeMesh_get_subdivide_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCylinderMesh = GodotCylinderMesh GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotCylinderMesh where
        type BaseClass GodotCylinderMesh = GodotPrimitiveMesh
        super = coerce
bindCylinderMesh_set_top_radius
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "set_top_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_set_top_radius #-}

instance Method "set_top_radius" GodotCylinderMesh (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_set_top_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_get_top_radius
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "get_top_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_get_top_radius #-}

instance Method "get_top_radius" GodotCylinderMesh (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_get_top_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_set_bottom_radius
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "set_bottom_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_set_bottom_radius #-}

instance Method "set_bottom_radius" GodotCylinderMesh
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_set_bottom_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_get_bottom_radius
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "get_bottom_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_get_bottom_radius #-}

instance Method "get_bottom_radius" GodotCylinderMesh (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_get_bottom_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_set_height
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_set_height #-}

instance Method "set_height" GodotCylinderMesh (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_get_height
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_get_height #-}

instance Method "get_height" GodotCylinderMesh (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_set_radial_segments
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "set_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_set_radial_segments #-}

instance Method "set_radial_segments" GodotCylinderMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_set_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_get_radial_segments
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "get_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_get_radial_segments #-}

instance Method "get_radial_segments" GodotCylinderMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_get_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_set_rings
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "set_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_set_rings #-}

instance Method "set_rings" GodotCylinderMesh (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_set_rings (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderMesh_get_rings
  = unsafePerformIO $
      withCString "CylinderMesh" $
        \ clsNamePtr ->
          withCString "get_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderMesh_get_rings #-}

instance Method "get_rings" GodotCylinderMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderMesh_get_rings (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPlaneMesh = GodotPlaneMesh GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotPlaneMesh where
        type BaseClass GodotPlaneMesh = GodotPrimitiveMesh
        super = coerce
bindPlaneMesh_set_size
  = unsafePerformIO $
      withCString "PlaneMesh" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneMesh_set_size #-}

instance Method "set_size" GodotPlaneMesh (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneMesh_set_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPlaneMesh_get_size
  = unsafePerformIO $
      withCString "PlaneMesh" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneMesh_get_size #-}

instance Method "get_size" GodotPlaneMesh (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneMesh_get_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPlaneMesh_set_subdivide_width
  = unsafePerformIO $
      withCString "PlaneMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneMesh_set_subdivide_width #-}

instance Method "set_subdivide_width" GodotPlaneMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneMesh_set_subdivide_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPlaneMesh_get_subdivide_width
  = unsafePerformIO $
      withCString "PlaneMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneMesh_get_subdivide_width #-}

instance Method "get_subdivide_width" GodotPlaneMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneMesh_get_subdivide_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPlaneMesh_set_subdivide_depth
  = unsafePerformIO $
      withCString "PlaneMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneMesh_set_subdivide_depth #-}

instance Method "set_subdivide_depth" GodotPlaneMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneMesh_set_subdivide_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPlaneMesh_get_subdivide_depth
  = unsafePerformIO $
      withCString "PlaneMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneMesh_get_subdivide_depth #-}

instance Method "get_subdivide_depth" GodotPlaneMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneMesh_get_subdivide_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPrismMesh = GodotPrismMesh GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotPrismMesh where
        type BaseClass GodotPrismMesh = GodotPrimitiveMesh
        super = coerce
bindPrismMesh_set_left_to_right
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "set_left_to_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_set_left_to_right #-}

instance Method "set_left_to_right" GodotPrismMesh (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_set_left_to_right (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_get_left_to_right
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "get_left_to_right" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_get_left_to_right #-}

instance Method "get_left_to_right" GodotPrismMesh (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_get_left_to_right (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_set_size
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_set_size #-}

instance Method "set_size" GodotPrismMesh (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_set_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_get_size
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_get_size #-}

instance Method "get_size" GodotPrismMesh (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_get_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_set_subdivide_width
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_set_subdivide_width #-}

instance Method "set_subdivide_width" GodotPrismMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_set_subdivide_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_get_subdivide_width
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_get_subdivide_width #-}

instance Method "get_subdivide_width" GodotPrismMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_get_subdivide_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_set_subdivide_height
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_set_subdivide_height #-}

instance Method "set_subdivide_height" GodotPrismMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_set_subdivide_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_get_subdivide_height
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_get_subdivide_height #-}

instance Method "get_subdivide_height" GodotPrismMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_get_subdivide_height
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_set_subdivide_depth
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "set_subdivide_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_set_subdivide_depth #-}

instance Method "set_subdivide_depth" GodotPrismMesh (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_set_subdivide_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPrismMesh_get_subdivide_depth
  = unsafePerformIO $
      withCString "PrismMesh" $
        \ clsNamePtr ->
          withCString "get_subdivide_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPrismMesh_get_subdivide_depth #-}

instance Method "get_subdivide_depth" GodotPrismMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPrismMesh_get_subdivide_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotQuadMesh = GodotQuadMesh GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotQuadMesh where
        type BaseClass GodotQuadMesh = GodotPrimitiveMesh
        super = coerce
bindQuadMesh_set_size
  = unsafePerformIO $
      withCString "QuadMesh" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindQuadMesh_set_size #-}

instance Method "set_size" GodotQuadMesh (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindQuadMesh_set_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindQuadMesh_get_size
  = unsafePerformIO $
      withCString "QuadMesh" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindQuadMesh_get_size #-}

instance Method "get_size" GodotQuadMesh (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindQuadMesh_get_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSphereMesh = GodotSphereMesh GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotSphereMesh where
        type BaseClass GodotSphereMesh = GodotPrimitiveMesh
        super = coerce
bindSphereMesh_set_radius
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_set_radius #-}

instance Method "set_radius" GodotSphereMesh (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_get_radius
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_get_radius #-}

instance Method "get_radius" GodotSphereMesh (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_set_height
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_set_height #-}

instance Method "set_height" GodotSphereMesh (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_get_height
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_get_height #-}

instance Method "get_height" GodotSphereMesh (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_set_radial_segments
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "set_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_set_radial_segments #-}

instance Method "set_radial_segments" GodotSphereMesh
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_set_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_get_radial_segments
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "get_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_get_radial_segments #-}

instance Method "get_radial_segments" GodotSphereMesh (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_get_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_set_rings
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "set_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_set_rings #-}

instance Method "set_rings" GodotSphereMesh (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_set_rings (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_get_rings
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "get_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_get_rings #-}

instance Method "get_rings" GodotSphereMesh (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_get_rings (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_set_is_hemisphere
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "set_is_hemisphere" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_set_is_hemisphere #-}

instance Method "set_is_hemisphere" GodotSphereMesh (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_set_is_hemisphere
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereMesh_get_is_hemisphere
  = unsafePerformIO $
      withCString "SphereMesh" $
        \ clsNamePtr ->
          withCString "get_is_hemisphere" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereMesh_get_is_hemisphere #-}

instance Method "get_is_hemisphere" GodotSphereMesh (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereMesh_get_is_hemisphere
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpatialMaterial = GodotSpatialMaterial GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotSpatialMaterial where
        type BaseClass GodotSpatialMaterial = GodotMaterial
        super = coerce
bindSpatialMaterial_set_albedo
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_albedo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_albedo #-}

instance Method "set_albedo" GodotSpatialMaterial
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_albedo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_albedo
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_albedo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_albedo #-}

instance Method "get_albedo" GodotSpatialMaterial (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_albedo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_specular
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_specular" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_specular #-}

instance Method "set_specular" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_specular
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_specular
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_specular" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_specular #-}

instance Method "get_specular" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_specular
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_metallic
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_metallic" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_metallic #-}

instance Method "set_metallic" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_metallic
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_metallic
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_metallic" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_metallic #-}

instance Method "get_metallic" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_metallic
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_roughness
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_roughness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_roughness #-}

instance Method "set_roughness" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_roughness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_roughness
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_roughness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_roughness #-}

instance Method "get_roughness" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_roughness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_emission
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_emission" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_emission #-}

instance Method "set_emission" GodotSpatialMaterial
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_emission
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_emission
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_emission" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_emission #-}

instance Method "get_emission" GodotSpatialMaterial (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_emission
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_emission_energy
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_emission_energy #-}

instance Method "set_emission_energy" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_emission_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_emission_energy
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_emission_energy #-}

instance Method "get_emission_energy" GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_emission_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_normal_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_normal_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_normal_scale #-}

instance Method "set_normal_scale" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_normal_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_normal_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_normal_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_normal_scale #-}

instance Method "get_normal_scale" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_normal_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_rim
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_rim" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_rim #-}

instance Method "set_rim" GodotSpatialMaterial (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_rim (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_rim
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_rim" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_rim #-}

instance Method "get_rim" GodotSpatialMaterial (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_rim (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_rim_tint
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_rim_tint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_rim_tint #-}

instance Method "set_rim_tint" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_rim_tint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_rim_tint
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_rim_tint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_rim_tint #-}

instance Method "get_rim_tint" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_rim_tint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_clearcoat
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_clearcoat" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_clearcoat #-}

instance Method "set_clearcoat" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_clearcoat
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_clearcoat
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_clearcoat" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_clearcoat #-}

instance Method "get_clearcoat" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_clearcoat
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_clearcoat_gloss
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_clearcoat_gloss" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_clearcoat_gloss #-}

instance Method "set_clearcoat_gloss" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_clearcoat_gloss
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_clearcoat_gloss
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_clearcoat_gloss" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_clearcoat_gloss #-}

instance Method "get_clearcoat_gloss" GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_clearcoat_gloss
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_anisotropy
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_anisotropy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_anisotropy #-}

instance Method "set_anisotropy" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_anisotropy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_anisotropy
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_anisotropy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_anisotropy #-}

instance Method "get_anisotropy" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_anisotropy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_depth_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_depth_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_depth_scale #-}

instance Method "set_depth_scale" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_depth_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_depth_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_depth_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_depth_scale #-}

instance Method "get_depth_scale" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_depth_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_subsurface_scattering_strength
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_subsurface_scattering_strength" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_subsurface_scattering_strength
             #-}

instance Method "set_subsurface_scattering_strength"
           GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_subsurface_scattering_strength
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_subsurface_scattering_strength
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_subsurface_scattering_strength" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_subsurface_scattering_strength
             #-}

instance Method "get_subsurface_scattering_strength"
           GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_subsurface_scattering_strength
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_transmission
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_transmission" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_transmission #-}

instance Method "set_transmission" GodotSpatialMaterial
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_transmission
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_transmission
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_transmission" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_transmission #-}

instance Method "get_transmission" GodotSpatialMaterial
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_transmission
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_refraction
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_refraction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_refraction #-}

instance Method "set_refraction" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_refraction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_refraction
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_refraction" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_refraction #-}

instance Method "get_refraction" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_refraction
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_line_width
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_line_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_line_width #-}

instance Method "set_line_width" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_line_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_line_width
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_line_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_line_width #-}

instance Method "get_line_width" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_line_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_point_size
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_point_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_point_size #-}

instance Method "set_point_size" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_point_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_point_size
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_point_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_point_size #-}

instance Method "get_point_size" GodotSpatialMaterial (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_point_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_detail_uv
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_detail_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_detail_uv #-}

instance Method "set_detail_uv" GodotSpatialMaterial (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_detail_uv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_detail_uv
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_detail_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_detail_uv #-}

instance Method "get_detail_uv" GodotSpatialMaterial (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_detail_uv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_blend_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_blend_mode #-}

instance Method "set_blend_mode" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_blend_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_blend_mode #-}

instance Method "get_blend_mode" GodotSpatialMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_depth_draw_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_depth_draw_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_depth_draw_mode #-}

instance Method "set_depth_draw_mode" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_depth_draw_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_depth_draw_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_depth_draw_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_depth_draw_mode #-}

instance Method "get_depth_draw_mode" GodotSpatialMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_depth_draw_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_cull_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_cull_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_cull_mode #-}

instance Method "set_cull_mode" GodotSpatialMaterial (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_cull_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_cull_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_cull_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_cull_mode #-}

instance Method "get_cull_mode" GodotSpatialMaterial (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_cull_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_diffuse_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_diffuse_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_diffuse_mode #-}

instance Method "set_diffuse_mode" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_diffuse_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_diffuse_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_diffuse_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_diffuse_mode #-}

instance Method "get_diffuse_mode" GodotSpatialMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_diffuse_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_specular_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_specular_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_specular_mode #-}

instance Method "set_specular_mode" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_specular_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_specular_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_specular_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_specular_mode #-}

instance Method "get_specular_mode" GodotSpatialMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_specular_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_flag
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_flag #-}

instance Method "set_flag" GodotSpatialMaterial
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_flag
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_flag" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_flag #-}

instance Method "get_flag" GodotSpatialMaterial (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_flag (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_feature
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_feature" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_feature #-}

instance Method "set_feature" GodotSpatialMaterial
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_feature (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_feature
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_feature" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_feature #-}

instance Method "get_feature" GodotSpatialMaterial (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_feature (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_texture
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_texture #-}

instance Method "set_texture" GodotSpatialMaterial
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_texture
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_texture #-}

instance Method "get_texture" GodotSpatialMaterial
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_detail_blend_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_detail_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_detail_blend_mode #-}

instance Method "set_detail_blend_mode" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_detail_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_detail_blend_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_detail_blend_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_detail_blend_mode #-}

instance Method "get_detail_blend_mode" GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_detail_blend_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_uv1_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_uv1_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_uv1_scale #-}

instance Method "set_uv1_scale" GodotSpatialMaterial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_uv1_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_uv1_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_uv1_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_uv1_scale #-}

instance Method "get_uv1_scale" GodotSpatialMaterial
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_uv1_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_uv1_offset
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_uv1_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_uv1_offset #-}

instance Method "set_uv1_offset" GodotSpatialMaterial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_uv1_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_uv1_offset
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_uv1_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_uv1_offset #-}

instance Method "get_uv1_offset" GodotSpatialMaterial
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_uv1_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_uv1_triplanar_blend_sharpness
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_uv1_triplanar_blend_sharpness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_uv1_triplanar_blend_sharpness
             #-}

instance Method "set_uv1_triplanar_blend_sharpness"
           GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_uv1_triplanar_blend_sharpness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_uv1_triplanar_blend_sharpness
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_uv1_triplanar_blend_sharpness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_uv1_triplanar_blend_sharpness
             #-}

instance Method "get_uv1_triplanar_blend_sharpness"
           GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_uv1_triplanar_blend_sharpness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_uv2_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_uv2_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_uv2_scale #-}

instance Method "set_uv2_scale" GodotSpatialMaterial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_uv2_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_uv2_scale
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_uv2_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_uv2_scale #-}

instance Method "get_uv2_scale" GodotSpatialMaterial
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_uv2_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_uv2_offset
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_uv2_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_uv2_offset #-}

instance Method "set_uv2_offset" GodotSpatialMaterial
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_uv2_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_uv2_offset
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_uv2_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_uv2_offset #-}

instance Method "get_uv2_offset" GodotSpatialMaterial
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_uv2_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_uv2_triplanar_blend_sharpness
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_uv2_triplanar_blend_sharpness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_uv2_triplanar_blend_sharpness
             #-}

instance Method "set_uv2_triplanar_blend_sharpness"
           GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_uv2_triplanar_blend_sharpness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_uv2_triplanar_blend_sharpness
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_uv2_triplanar_blend_sharpness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_uv2_triplanar_blend_sharpness
             #-}

instance Method "get_uv2_triplanar_blend_sharpness"
           GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_uv2_triplanar_blend_sharpness
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_billboard_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_billboard_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_billboard_mode #-}

instance Method "set_billboard_mode" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_billboard_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_billboard_mode
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_billboard_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_billboard_mode #-}

instance Method "get_billboard_mode" GodotSpatialMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_billboard_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_particles_anim_h_frames
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_particles_anim_h_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_particles_anim_h_frames #-}

instance Method "set_particles_anim_h_frames" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_particles_anim_h_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_particles_anim_h_frames
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_particles_anim_h_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_particles_anim_h_frames #-}

instance Method "get_particles_anim_h_frames" GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_particles_anim_h_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_particles_anim_v_frames
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_particles_anim_v_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_particles_anim_v_frames #-}

instance Method "set_particles_anim_v_frames" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_particles_anim_v_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_particles_anim_v_frames
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_particles_anim_v_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_particles_anim_v_frames #-}

instance Method "get_particles_anim_v_frames" GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_particles_anim_v_frames
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_particles_anim_loop
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_particles_anim_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_particles_anim_loop #-}

instance Method "set_particles_anim_loop" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_particles_anim_loop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_particles_anim_loop
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_particles_anim_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_particles_anim_loop #-}

instance Method "get_particles_anim_loop" GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_particles_anim_loop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_depth_deep_parallax
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_depth_deep_parallax" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_depth_deep_parallax #-}

instance Method "set_depth_deep_parallax" GodotSpatialMaterial
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_depth_deep_parallax
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_is_depth_deep_parallax_enabled
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "is_depth_deep_parallax_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_is_depth_deep_parallax_enabled #-}

instance Method "is_depth_deep_parallax_enabled"
           GodotSpatialMaterial
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_is_depth_deep_parallax_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_depth_deep_parallax_min_layers
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_depth_deep_parallax_min_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_depth_deep_parallax_min_layers
             #-}

instance Method "set_depth_deep_parallax_min_layers"
           GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_depth_deep_parallax_min_layers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_depth_deep_parallax_min_layers
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_depth_deep_parallax_min_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_depth_deep_parallax_min_layers
             #-}

instance Method "get_depth_deep_parallax_min_layers"
           GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_depth_deep_parallax_min_layers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_depth_deep_parallax_max_layers
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_depth_deep_parallax_max_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_depth_deep_parallax_max_layers
             #-}

instance Method "set_depth_deep_parallax_max_layers"
           GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_depth_deep_parallax_max_layers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_depth_deep_parallax_max_layers
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_depth_deep_parallax_max_layers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_depth_deep_parallax_max_layers
             #-}

instance Method "get_depth_deep_parallax_max_layers"
           GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_depth_deep_parallax_max_layers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_grow
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_grow" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_grow #-}

instance Method "set_grow" GodotSpatialMaterial (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_grow (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_grow
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_grow" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_grow #-}

instance Method "get_grow" GodotSpatialMaterial (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_grow (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_emission_operator
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_emission_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_emission_operator #-}

instance Method "set_emission_operator" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_emission_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_emission_operator
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_emission_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_emission_operator #-}

instance Method "get_emission_operator" GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_emission_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_ao_light_affect
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_ao_light_affect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_ao_light_affect #-}

instance Method "set_ao_light_affect" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_ao_light_affect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_ao_light_affect
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_ao_light_affect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_ao_light_affect #-}

instance Method "get_ao_light_affect" GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_ao_light_affect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_alpha_scissor_threshold
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_alpha_scissor_threshold" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_alpha_scissor_threshold #-}

instance Method "set_alpha_scissor_threshold" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_alpha_scissor_threshold
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_alpha_scissor_threshold
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_alpha_scissor_threshold" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_alpha_scissor_threshold #-}

instance Method "get_alpha_scissor_threshold" GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_alpha_scissor_threshold
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_grow_enabled
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_grow_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_grow_enabled #-}

instance Method "set_grow_enabled" GodotSpatialMaterial
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_grow_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_is_grow_enabled
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "is_grow_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_is_grow_enabled #-}

instance Method "is_grow_enabled" GodotSpatialMaterial (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_is_grow_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_metallic_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_metallic_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_metallic_texture_channel #-}

instance Method "set_metallic_texture_channel" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_metallic_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_metallic_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_metallic_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_metallic_texture_channel #-}

instance Method "get_metallic_texture_channel" GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_metallic_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_roughness_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_roughness_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_roughness_texture_channel #-}

instance Method "set_roughness_texture_channel"
           GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_roughness_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_roughness_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_roughness_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_roughness_texture_channel #-}

instance Method "get_roughness_texture_channel"
           GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_roughness_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_ao_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_ao_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_ao_texture_channel #-}

instance Method "set_ao_texture_channel" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_ao_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_ao_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_ao_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_ao_texture_channel #-}

instance Method "get_ao_texture_channel" GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_ao_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_refraction_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_refraction_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_refraction_texture_channel #-}

instance Method "set_refraction_texture_channel"
           GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_refraction_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_refraction_texture_channel
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_refraction_texture_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_refraction_texture_channel #-}

instance Method "get_refraction_texture_channel"
           GodotSpatialMaterial
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_refraction_texture_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_proximity_fade
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_proximity_fade" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_proximity_fade #-}

instance Method "set_proximity_fade" GodotSpatialMaterial
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_proximity_fade
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_is_proximity_fade_enabled
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "is_proximity_fade_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_is_proximity_fade_enabled #-}

instance Method "is_proximity_fade_enabled" GodotSpatialMaterial
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_is_proximity_fade_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_proximity_fade_distance
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_proximity_fade_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_proximity_fade_distance #-}

instance Method "set_proximity_fade_distance" GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_proximity_fade_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_proximity_fade_distance
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_proximity_fade_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_proximity_fade_distance #-}

instance Method "get_proximity_fade_distance" GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_proximity_fade_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_distance_fade
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_distance_fade" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_distance_fade #-}

instance Method "set_distance_fade" GodotSpatialMaterial
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_set_distance_fade
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_distance_fade
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_distance_fade" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_distance_fade #-}

instance Method "get_distance_fade" GodotSpatialMaterial (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialMaterial_get_distance_fade
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_distance_fade_max_distance
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_distance_fade_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_distance_fade_max_distance #-}

instance Method "set_distance_fade_max_distance"
           GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_distance_fade_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_distance_fade_max_distance
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_distance_fade_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_distance_fade_max_distance #-}

instance Method "get_distance_fade_max_distance"
           GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_distance_fade_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_set_distance_fade_min_distance
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "set_distance_fade_min_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_set_distance_fade_min_distance #-}

instance Method "set_distance_fade_min_distance"
           GodotSpatialMaterial
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_set_distance_fade_min_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialMaterial_get_distance_fade_min_distance
  = unsafePerformIO $
      withCString "SpatialMaterial" $
        \ clsNamePtr ->
          withCString "get_distance_fade_min_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialMaterial_get_distance_fade_min_distance #-}

instance Method "get_distance_fade_min_distance"
           GodotSpatialMaterial
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialMaterial_get_distance_fade_min_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRayShape = GodotRayShape GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotRayShape where
        type BaseClass GodotRayShape = GodotShape
        super = coerce
bindRayShape_set_length
  = unsafePerformIO $
      withCString "RayShape" $
        \ clsNamePtr ->
          withCString "set_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape_set_length #-}

instance Method "set_length" GodotRayShape (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape_set_length (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayShape_get_length
  = unsafePerformIO $
      withCString "RayShape" $
        \ clsNamePtr ->
          withCString "get_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape_get_length #-}

instance Method "get_length" GodotRayShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape_get_length (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayShape_set_slips_on_slope
  = unsafePerformIO $
      withCString "RayShape" $
        \ clsNamePtr ->
          withCString "set_slips_on_slope" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape_set_slips_on_slope #-}

instance Method "set_slips_on_slope" GodotRayShape (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape_set_slips_on_slope (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayShape_get_slips_on_slope
  = unsafePerformIO $
      withCString "RayShape" $
        \ clsNamePtr ->
          withCString "get_slips_on_slope" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape_get_slips_on_slope #-}

instance Method "get_slips_on_slope" GodotRayShape (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape_get_slips_on_slope (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSphereShape = GodotSphereShape GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotSphereShape where
        type BaseClass GodotSphereShape = GodotShape
        super = coerce
bindSphereShape_set_radius
  = unsafePerformIO $
      withCString "SphereShape" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereShape_set_radius #-}

instance Method "set_radius" GodotSphereShape (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereShape_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSphereShape_get_radius
  = unsafePerformIO $
      withCString "SphereShape" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSphereShape_get_radius #-}

instance Method "get_radius" GodotSphereShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSphereShape_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBoxShape = GodotBoxShape GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotBoxShape where
        type BaseClass GodotBoxShape = GodotShape
        super = coerce
bindBoxShape_set_extents
  = unsafePerformIO $
      withCString "BoxShape" $
        \ clsNamePtr ->
          withCString "set_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBoxShape_set_extents #-}

instance Method "set_extents" GodotBoxShape (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBoxShape_set_extents (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBoxShape_get_extents
  = unsafePerformIO $
      withCString "BoxShape" $
        \ clsNamePtr ->
          withCString "get_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBoxShape_get_extents #-}

instance Method "get_extents" GodotBoxShape (IO GodotVector3) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBoxShape_get_extents (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCapsuleShape = GodotCapsuleShape GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotCapsuleShape where
        type BaseClass GodotCapsuleShape = GodotShape
        super = coerce
bindCapsuleShape_set_radius
  = unsafePerformIO $
      withCString "CapsuleShape" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape_set_radius #-}

instance Method "set_radius" GodotCapsuleShape (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleShape_get_radius
  = unsafePerformIO $
      withCString "CapsuleShape" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape_get_radius #-}

instance Method "get_radius" GodotCapsuleShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleShape_set_height
  = unsafePerformIO $
      withCString "CapsuleShape" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape_set_height #-}

instance Method "set_height" GodotCapsuleShape (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleShape_get_height
  = unsafePerformIO $
      withCString "CapsuleShape" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape_get_height #-}

instance Method "get_height" GodotCapsuleShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCylinderShape = GodotCylinderShape GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotCylinderShape where
        type BaseClass GodotCylinderShape = GodotShape
        super = coerce
bindCylinderShape_set_radius
  = unsafePerformIO $
      withCString "CylinderShape" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderShape_set_radius #-}

instance Method "set_radius" GodotCylinderShape (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderShape_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderShape_get_radius
  = unsafePerformIO $
      withCString "CylinderShape" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderShape_get_radius #-}

instance Method "get_radius" GodotCylinderShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderShape_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderShape_set_height
  = unsafePerformIO $
      withCString "CylinderShape" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderShape_set_height #-}

instance Method "set_height" GodotCylinderShape (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderShape_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCylinderShape_get_height
  = unsafePerformIO $
      withCString "CylinderShape" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCylinderShape_get_height #-}

instance Method "get_height" GodotCylinderShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCylinderShape_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPlaneShape = GodotPlaneShape GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotPlaneShape where
        type BaseClass GodotPlaneShape = GodotShape
        super = coerce
bindPlaneShape_set_plane
  = unsafePerformIO $
      withCString "PlaneShape" $
        \ clsNamePtr ->
          withCString "set_plane" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneShape_set_plane #-}

instance Method "set_plane" GodotPlaneShape (GodotPlane -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneShape_set_plane (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPlaneShape_get_plane
  = unsafePerformIO $
      withCString "PlaneShape" $
        \ clsNamePtr ->
          withCString "get_plane" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPlaneShape_get_plane #-}

instance Method "get_plane" GodotPlaneShape (IO GodotPlane) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPlaneShape_get_plane (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotConvexPolygonShape = GodotConvexPolygonShape GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotConvexPolygonShape where
        type BaseClass GodotConvexPolygonShape = GodotShape
        super = coerce
bindConvexPolygonShape_set_points
  = unsafePerformIO $
      withCString "ConvexPolygonShape" $
        \ clsNamePtr ->
          withCString "set_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConvexPolygonShape_set_points #-}

instance Method "set_points" GodotConvexPolygonShape
           (GodotPoolVector3Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConvexPolygonShape_set_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConvexPolygonShape_get_points
  = unsafePerformIO $
      withCString "ConvexPolygonShape" $
        \ clsNamePtr ->
          withCString "get_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConvexPolygonShape_get_points #-}

instance Method "get_points" GodotConvexPolygonShape
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConvexPolygonShape_get_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotConcavePolygonShape = GodotConcavePolygonShape GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotConcavePolygonShape where
        type BaseClass GodotConcavePolygonShape = GodotShape
        super = coerce
bindConcavePolygonShape_set_faces
  = unsafePerformIO $
      withCString "ConcavePolygonShape" $
        \ clsNamePtr ->
          withCString "set_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConcavePolygonShape_set_faces #-}

instance Method "set_faces" GodotConcavePolygonShape
           (GodotPoolVector3Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConcavePolygonShape_set_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConcavePolygonShape_get_faces
  = unsafePerformIO $
      withCString "ConcavePolygonShape" $
        \ clsNamePtr ->
          withCString "get_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConcavePolygonShape_get_faces #-}

instance Method "get_faces" GodotConcavePolygonShape
           (IO GodotPoolVector3Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConcavePolygonShape_get_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSurfaceTool = GodotSurfaceTool GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotSurfaceTool where
        type BaseClass GodotSurfaceTool = GodotReference
        super = coerce
bindSurfaceTool_begin
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_begin #-}

instance Method "begin" GodotSurfaceTool (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_begin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_vertex
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_vertex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_vertex #-}

instance Method "add_vertex" GodotSurfaceTool
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_vertex (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_color
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_color #-}

instance Method "add_color" GodotSurfaceTool (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_normal
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_normal #-}

instance Method "add_normal" GodotSurfaceTool
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_normal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_tangent
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_tangent #-}

instance Method "add_tangent" GodotSurfaceTool
           (GodotPlane -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_tangent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_uv
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_uv #-}

instance Method "add_uv" GodotSurfaceTool (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_uv (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_uv2
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_uv2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_uv2 #-}

instance Method "add_uv2" GodotSurfaceTool (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_uv2 (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_bones
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_bones" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_bones #-}

instance Method "add_bones" GodotSurfaceTool
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_bones (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_weights
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_weights" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_weights #-}

instance Method "add_weights" GodotSurfaceTool
           (GodotPoolRealArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_weights (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_smooth_group
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_smooth_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_smooth_group #-}

instance Method "add_smooth_group" GodotSurfaceTool (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_smooth_group
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_triangle_fan
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_triangle_fan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_triangle_fan #-}

instance Method "add_triangle_fan" GodotSurfaceTool
           (GodotPoolVector3Array ->
              GodotPoolVector2Array ->
                GodotPoolColorArray ->
                  GodotPoolVector2Array ->
                    GodotPoolVector3Array -> GodotArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_triangle_fan
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_index
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_index #-}

instance Method "add_index" GodotSurfaceTool (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_index (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_index
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_index #-}

instance Method "index" GodotSurfaceTool (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_index (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_deindex
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "deindex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_deindex #-}

instance Method "deindex" GodotSurfaceTool (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_deindex (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_generate_normals
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "generate_normals" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_generate_normals #-}

instance Method "generate_normals" GodotSurfaceTool (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_generate_normals
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_generate_tangents
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "generate_tangents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_generate_tangents #-}

instance Method "generate_tangents" GodotSurfaceTool (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_generate_tangents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_add_to_format
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "add_to_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_add_to_format #-}

instance Method "add_to_format" GodotSurfaceTool (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_add_to_format (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_set_material
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_set_material #-}

instance Method "set_material" GodotSurfaceTool
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_clear
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_clear #-}

instance Method "clear" GodotSurfaceTool (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_create_from
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "create_from" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_create_from #-}

instance Method "create_from" GodotSurfaceTool
           (GodotMesh -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_create_from (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_append_from
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "append_from" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_append_from #-}

instance Method "append_from" GodotSurfaceTool
           (GodotMesh -> Int -> GodotTransform -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_append_from (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSurfaceTool_commit
  = unsafePerformIO $
      withCString "SurfaceTool" $
        \ clsNamePtr ->
          withCString "commit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSurfaceTool_commit #-}

instance Method "commit" GodotSurfaceTool
           (GodotArrayMesh -> Int -> IO GodotArrayMesh)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSurfaceTool_commit (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMeshDataTool = GodotMeshDataTool GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotMeshDataTool where
        type BaseClass GodotMeshDataTool = GodotReference
        super = coerce
bindMeshDataTool_clear
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_clear #-}

instance Method "clear" GodotMeshDataTool (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_create_from_surface
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "create_from_surface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_create_from_surface #-}

instance Method "create_from_surface" GodotMeshDataTool
           (GodotArrayMesh -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_create_from_surface
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_commit_to_surface
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "commit_to_surface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_commit_to_surface #-}

instance Method "commit_to_surface" GodotMeshDataTool
           (GodotArrayMesh -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_commit_to_surface
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_format
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_format #-}

instance Method "get_format" GodotMeshDataTool (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_format (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_count
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_count #-}

instance Method "get_vertex_count" GodotMeshDataTool (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_edge_count
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_edge_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_edge_count #-}

instance Method "get_edge_count" GodotMeshDataTool (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_edge_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_face_count
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_face_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_face_count #-}

instance Method "get_face_count" GodotMeshDataTool (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_face_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex #-}

instance Method "set_vertex" GodotMeshDataTool
           (Int -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex #-}

instance Method "get_vertex" GodotMeshDataTool
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_normal
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_normal #-}

instance Method "set_vertex_normal" GodotMeshDataTool
           (Int -> GodotVector3 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_normal
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_normal #-}

instance Method "get_vertex_normal" GodotMeshDataTool
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_tangent
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_tangent #-}

instance Method "set_vertex_tangent" GodotMeshDataTool
           (Int -> GodotPlane -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_tangent
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_tangent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_tangent #-}

instance Method "get_vertex_tangent" GodotMeshDataTool
           (Int -> IO GodotPlane)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_tangent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_uv
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_uv #-}

instance Method "set_vertex_uv" GodotMeshDataTool
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_uv (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_uv
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_uv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_uv #-}

instance Method "get_vertex_uv" GodotMeshDataTool
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_uv (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_uv2
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_uv2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_uv2 #-}

instance Method "set_vertex_uv2" GodotMeshDataTool
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_uv2 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_uv2
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_uv2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_uv2 #-}

instance Method "get_vertex_uv2" GodotMeshDataTool
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_uv2 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_color
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_color #-}

instance Method "set_vertex_color" GodotMeshDataTool
           (Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_color
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_color #-}

instance Method "get_vertex_color" GodotMeshDataTool
           (Int -> IO GodotColor)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_bones
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_bones" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_bones #-}

instance Method "set_vertex_bones" GodotMeshDataTool
           (Int -> GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_bones
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_bones
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_bones" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_bones #-}

instance Method "get_vertex_bones" GodotMeshDataTool
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_bones
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_weights
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_weights" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_weights #-}

instance Method "set_vertex_weights" GodotMeshDataTool
           (Int -> GodotPoolRealArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_weights
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_weights
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_weights" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_weights #-}

instance Method "get_vertex_weights" GodotMeshDataTool
           (Int -> IO GodotPoolRealArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_weights
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_vertex_meta
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_vertex_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_vertex_meta #-}

instance Method "set_vertex_meta" GodotMeshDataTool
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_vertex_meta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_meta
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_meta #-}

instance Method "get_vertex_meta" GodotMeshDataTool
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_meta
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_edges
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_edges" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_edges #-}

instance Method "get_vertex_edges" GodotMeshDataTool
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_edges
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_vertex_faces
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_vertex_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_vertex_faces #-}

instance Method "get_vertex_faces" GodotMeshDataTool
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_vertex_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_edge_vertex
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_edge_vertex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_edge_vertex #-}

instance Method "get_edge_vertex" GodotMeshDataTool
           (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_edge_vertex
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_edge_faces
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_edge_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_edge_faces #-}

instance Method "get_edge_faces" GodotMeshDataTool
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_edge_faces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_edge_meta
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_edge_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_edge_meta #-}

instance Method "set_edge_meta" GodotMeshDataTool
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_edge_meta (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_edge_meta
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_edge_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_edge_meta #-}

instance Method "get_edge_meta" GodotMeshDataTool
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_edge_meta (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_face_vertex
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_face_vertex" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_face_vertex #-}

instance Method "get_face_vertex" GodotMeshDataTool
           (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_face_vertex
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_face_edge
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_face_edge" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_face_edge #-}

instance Method "get_face_edge" GodotMeshDataTool
           (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_face_edge (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_face_meta
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_face_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_face_meta #-}

instance Method "set_face_meta" GodotMeshDataTool
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_face_meta (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_face_meta
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_face_meta" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_face_meta #-}

instance Method "get_face_meta" GodotMeshDataTool
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_face_meta (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_face_normal
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_face_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_face_normal #-}

instance Method "get_face_normal" GodotMeshDataTool
           (Int -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_face_normal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_set_material
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_set_material #-}

instance Method "set_material" GodotMeshDataTool
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMeshDataTool_get_material
  = unsafePerformIO $
      withCString "MeshDataTool" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMeshDataTool_get_material #-}

instance Method "get_material" GodotMeshDataTool (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMeshDataTool_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSpatialVelocityTracker = GodotSpatialVelocityTracker GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotSpatialVelocityTracker where
        type BaseClass GodotSpatialVelocityTracker = GodotReference
        super = coerce
bindSpatialVelocityTracker_set_track_physics_step
  = unsafePerformIO $
      withCString "SpatialVelocityTracker" $
        \ clsNamePtr ->
          withCString "set_track_physics_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialVelocityTracker_set_track_physics_step #-}

instance Method "set_track_physics_step"
           GodotSpatialVelocityTracker
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialVelocityTracker_set_track_physics_step
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialVelocityTracker_is_tracking_physics_step
  = unsafePerformIO $
      withCString "SpatialVelocityTracker" $
        \ clsNamePtr ->
          withCString "is_tracking_physics_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialVelocityTracker_is_tracking_physics_step
             #-}

instance Method "is_tracking_physics_step"
           GodotSpatialVelocityTracker
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialVelocityTracker_is_tracking_physics_step
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialVelocityTracker_update_position
  = unsafePerformIO $
      withCString "SpatialVelocityTracker" $
        \ clsNamePtr ->
          withCString "update_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialVelocityTracker_update_position #-}

instance Method "update_position" GodotSpatialVelocityTracker
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialVelocityTracker_update_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialVelocityTracker_get_tracked_linear_velocity
  = unsafePerformIO $
      withCString "SpatialVelocityTracker" $
        \ clsNamePtr ->
          withCString "get_tracked_linear_velocity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialVelocityTracker_get_tracked_linear_velocity
             #-}

instance Method "get_tracked_linear_velocity"
           GodotSpatialVelocityTracker
           (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSpatialVelocityTracker_get_tracked_linear_velocity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSpatialVelocityTracker_reset
  = unsafePerformIO $
      withCString "SpatialVelocityTracker" $
        \ clsNamePtr ->
          withCString "reset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSpatialVelocityTracker_reset #-}

instance Method "reset" GodotSpatialVelocityTracker
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSpatialVelocityTracker_reset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSky = GodotSky GodotObject
                     deriving newtype AsVariant

instance HasBaseClass GodotSky where
        type BaseClass GodotSky = GodotResource
        super = coerce
bindSky_set_radiance_size
  = unsafePerformIO $
      withCString "Sky" $
        \ clsNamePtr ->
          withCString "set_radiance_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSky_set_radiance_size #-}

instance Method "set_radiance_size" GodotSky (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSky_set_radiance_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSky_get_radiance_size
  = unsafePerformIO $
      withCString "Sky" $
        \ clsNamePtr ->
          withCString "get_radiance_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSky_get_radiance_size #-}

instance Method "get_radiance_size" GodotSky (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSky_get_radiance_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPanoramaSky = GodotPanoramaSky GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotPanoramaSky where
        type BaseClass GodotPanoramaSky = GodotSky
        super = coerce
bindPanoramaSky_set_panorama
  = unsafePerformIO $
      withCString "PanoramaSky" $
        \ clsNamePtr ->
          withCString "set_panorama" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPanoramaSky_set_panorama #-}

instance Method "set_panorama" GodotPanoramaSky
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPanoramaSky_set_panorama (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPanoramaSky_get_panorama
  = unsafePerformIO $
      withCString "PanoramaSky" $
        \ clsNamePtr ->
          withCString "get_panorama" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPanoramaSky_get_panorama #-}

instance Method "get_panorama" GodotPanoramaSky (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPanoramaSky_get_panorama (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotProceduralSky = GodotProceduralSky GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotProceduralSky where
        type BaseClass GodotProceduralSky = GodotSky
        super = coerce
bindProceduralSky__update_sky
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "_update_sky" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky__update_sky #-}

instance Method "_update_sky" GodotProceduralSky (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky__update_sky (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sky_top_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sky_top_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sky_top_color #-}

instance Method "set_sky_top_color" GodotProceduralSky
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sky_top_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sky_top_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sky_top_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sky_top_color #-}

instance Method "get_sky_top_color" GodotProceduralSky
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sky_top_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sky_horizon_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sky_horizon_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sky_horizon_color #-}

instance Method "set_sky_horizon_color" GodotProceduralSky
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sky_horizon_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sky_horizon_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sky_horizon_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sky_horizon_color #-}

instance Method "get_sky_horizon_color" GodotProceduralSky
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sky_horizon_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sky_curve
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sky_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sky_curve #-}

instance Method "set_sky_curve" GodotProceduralSky (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sky_curve (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sky_curve
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sky_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sky_curve #-}

instance Method "get_sky_curve" GodotProceduralSky (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sky_curve (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sky_energy
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sky_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sky_energy #-}

instance Method "set_sky_energy" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sky_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sky_energy
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sky_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sky_energy #-}

instance Method "get_sky_energy" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sky_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_ground_bottom_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_ground_bottom_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_ground_bottom_color #-}

instance Method "set_ground_bottom_color" GodotProceduralSky
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_ground_bottom_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_ground_bottom_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_ground_bottom_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_ground_bottom_color #-}

instance Method "get_ground_bottom_color" GodotProceduralSky
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_ground_bottom_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_ground_horizon_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_ground_horizon_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_ground_horizon_color #-}

instance Method "set_ground_horizon_color" GodotProceduralSky
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_ground_horizon_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_ground_horizon_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_ground_horizon_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_ground_horizon_color #-}

instance Method "get_ground_horizon_color" GodotProceduralSky
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_ground_horizon_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_ground_curve
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_ground_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_ground_curve #-}

instance Method "set_ground_curve" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_ground_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_ground_curve
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_ground_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_ground_curve #-}

instance Method "get_ground_curve" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_ground_curve
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_ground_energy
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_ground_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_ground_energy #-}

instance Method "set_ground_energy" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_ground_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_ground_energy
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_ground_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_ground_energy #-}

instance Method "get_ground_energy" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_ground_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sun_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sun_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sun_color #-}

instance Method "set_sun_color" GodotProceduralSky
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sun_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sun_color
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sun_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sun_color #-}

instance Method "get_sun_color" GodotProceduralSky (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sun_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sun_latitude
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sun_latitude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sun_latitude #-}

instance Method "set_sun_latitude" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sun_latitude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sun_latitude
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sun_latitude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sun_latitude #-}

instance Method "get_sun_latitude" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sun_latitude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sun_longitude
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sun_longitude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sun_longitude #-}

instance Method "set_sun_longitude" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sun_longitude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sun_longitude
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sun_longitude" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sun_longitude #-}

instance Method "get_sun_longitude" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sun_longitude
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sun_angle_min
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sun_angle_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sun_angle_min #-}

instance Method "set_sun_angle_min" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sun_angle_min
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sun_angle_min
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sun_angle_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sun_angle_min #-}

instance Method "get_sun_angle_min" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sun_angle_min
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sun_angle_max
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sun_angle_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sun_angle_max #-}

instance Method "set_sun_angle_max" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sun_angle_max
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sun_angle_max
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sun_angle_max" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sun_angle_max #-}

instance Method "get_sun_angle_max" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sun_angle_max
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sun_curve
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sun_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sun_curve #-}

instance Method "set_sun_curve" GodotProceduralSky (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sun_curve (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sun_curve
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sun_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sun_curve #-}

instance Method "get_sun_curve" GodotProceduralSky (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sun_curve (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_sun_energy
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_sun_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_sun_energy #-}

instance Method "set_sun_energy" GodotProceduralSky
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_sun_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_sun_energy
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_sun_energy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_sun_energy #-}

instance Method "get_sun_energy" GodotProceduralSky (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_sun_energy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_set_texture_size
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "set_texture_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_set_texture_size #-}

instance Method "set_texture_size" GodotProceduralSky
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_set_texture_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky_get_texture_size
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "get_texture_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky_get_texture_size #-}

instance Method "get_texture_size" GodotProceduralSky (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky_get_texture_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProceduralSky__thread_done
  = unsafePerformIO $
      withCString "ProceduralSky" $
        \ clsNamePtr ->
          withCString "_thread_done" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProceduralSky__thread_done #-}

instance Method "_thread_done" GodotProceduralSky
           (GodotImage -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProceduralSky__thread_done (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStreamTexture = GodotStreamTexture GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotStreamTexture where
        type BaseClass GodotStreamTexture = GodotTexture
        super = coerce
bindStreamTexture_load
  = unsafePerformIO $
      withCString "StreamTexture" $
        \ clsNamePtr ->
          withCString "load" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamTexture_load #-}

instance Method "load" GodotStreamTexture (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamTexture_load (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStreamTexture_get_load_path
  = unsafePerformIO $
      withCString "StreamTexture" $
        \ clsNamePtr ->
          withCString "get_load_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStreamTexture_get_load_path #-}

instance Method "get_load_path" GodotStreamTexture (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStreamTexture_get_load_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotImageTexture = GodotImageTexture GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotImageTexture where
        type BaseClass GodotImageTexture = GodotTexture
        super = coerce
bindImageTexture_create
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_create #-}

instance Method "create" GodotImageTexture
           (Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_create (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_create_from_image
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "create_from_image" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_create_from_image #-}

instance Method "create_from_image" GodotImageTexture
           (GodotImage -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_create_from_image
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_get_format
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_get_format #-}

instance Method "get_format" GodotImageTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_get_format (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_load
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "load" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_load #-}

instance Method "load" GodotImageTexture (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_load (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_set_data
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_set_data #-}

instance Method "set_data" GodotImageTexture (GodotImage -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_set_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_set_storage
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "set_storage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_set_storage #-}

instance Method "set_storage" GodotImageTexture (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_set_storage (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_get_storage
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "get_storage" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_get_storage #-}

instance Method "get_storage" GodotImageTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_get_storage (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_set_lossy_storage_quality
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "set_lossy_storage_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_set_lossy_storage_quality #-}

instance Method "set_lossy_storage_quality" GodotImageTexture
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_set_lossy_storage_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_get_lossy_storage_quality
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "get_lossy_storage_quality" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_get_lossy_storage_quality #-}

instance Method "get_lossy_storage_quality" GodotImageTexture
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_get_lossy_storage_quality
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture_set_size_override
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "set_size_override" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture_set_size_override #-}

instance Method "set_size_override" GodotImageTexture
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture_set_size_override
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindImageTexture__reload_hook
  = unsafePerformIO $
      withCString "ImageTexture" $
        \ clsNamePtr ->
          withCString "_reload_hook" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindImageTexture__reload_hook #-}

instance Method "_reload_hook" GodotImageTexture
           (GodotRid -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindImageTexture__reload_hook (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAtlasTexture = GodotAtlasTexture GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotAtlasTexture where
        type BaseClass GodotAtlasTexture = GodotTexture
        super = coerce
bindAtlasTexture_set_atlas
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "set_atlas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_set_atlas #-}

instance Method "set_atlas" GodotAtlasTexture
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_set_atlas (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAtlasTexture_get_atlas
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "get_atlas" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_get_atlas #-}

instance Method "get_atlas" GodotAtlasTexture (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_get_atlas (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAtlasTexture_set_region
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "set_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_set_region #-}

instance Method "set_region" GodotAtlasTexture
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_set_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAtlasTexture_get_region
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "get_region" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_get_region #-}

instance Method "get_region" GodotAtlasTexture (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_get_region (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAtlasTexture_set_margin
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "set_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_set_margin #-}

instance Method "set_margin" GodotAtlasTexture
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_set_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAtlasTexture_get_margin
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_get_margin #-}

instance Method "get_margin" GodotAtlasTexture (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_get_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAtlasTexture_set_filter_clip
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "set_filter_clip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_set_filter_clip #-}

instance Method "set_filter_clip" GodotAtlasTexture (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_set_filter_clip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAtlasTexture_has_filter_clip
  = unsafePerformIO $
      withCString "AtlasTexture" $
        \ clsNamePtr ->
          withCString "has_filter_clip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAtlasTexture_has_filter_clip #-}

instance Method "has_filter_clip" GodotAtlasTexture (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAtlasTexture_has_filter_clip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotLargeTexture = GodotLargeTexture GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotLargeTexture where
        type BaseClass GodotLargeTexture = GodotTexture
        super = coerce
bindLargeTexture_add_piece
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "add_piece" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_add_piece #-}

instance Method "add_piece" GodotLargeTexture
           (GodotVector2 -> GodotTexture -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_add_piece (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture_set_piece_offset
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "set_piece_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_set_piece_offset #-}

instance Method "set_piece_offset" GodotLargeTexture
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_set_piece_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture_set_piece_texture
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "set_piece_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_set_piece_texture #-}

instance Method "set_piece_texture" GodotLargeTexture
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_set_piece_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture_set_size
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_set_size #-}

instance Method "set_size" GodotLargeTexture
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_set_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture_clear
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_clear #-}

instance Method "clear" GodotLargeTexture (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture_get_piece_count
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "get_piece_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_get_piece_count #-}

instance Method "get_piece_count" GodotLargeTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_get_piece_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture_get_piece_offset
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "get_piece_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_get_piece_offset #-}

instance Method "get_piece_offset" GodotLargeTexture
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_get_piece_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture_get_piece_texture
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "get_piece_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture_get_piece_texture #-}

instance Method "get_piece_texture" GodotLargeTexture
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture_get_piece_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture__set_data
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture__set_data #-}

instance Method "_set_data" GodotLargeTexture (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture__set_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLargeTexture__get_data
  = unsafePerformIO $
      withCString "LargeTexture" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLargeTexture__get_data #-}

instance Method "_get_data" GodotLargeTexture (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLargeTexture__get_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotProxyTexture = GodotProxyTexture GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotProxyTexture where
        type BaseClass GodotProxyTexture = GodotTexture
        super = coerce
bindProxyTexture_set_base
  = unsafePerformIO $
      withCString "ProxyTexture" $
        \ clsNamePtr ->
          withCString "set_base" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProxyTexture_set_base #-}

instance Method "set_base" GodotProxyTexture
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProxyTexture_set_base (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindProxyTexture_get_base
  = unsafePerformIO $
      withCString "ProxyTexture" $
        \ clsNamePtr ->
          withCString "get_base" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindProxyTexture_get_base #-}

instance Method "get_base" GodotProxyTexture (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindProxyTexture_get_base (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimatedTexture = GodotAnimatedTexture GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotAnimatedTexture where
        type BaseClass GodotAnimatedTexture = GodotTexture
        super = coerce
bindAnimatedTexture_set_frames
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "set_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_set_frames #-}

instance Method "set_frames" GodotAnimatedTexture (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_set_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture_get_frames
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "get_frames" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_get_frames #-}

instance Method "get_frames" GodotAnimatedTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_get_frames (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture_set_fps
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "set_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_set_fps #-}

instance Method "set_fps" GodotAnimatedTexture (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_set_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture_get_fps
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "get_fps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_get_fps #-}

instance Method "get_fps" GodotAnimatedTexture (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_get_fps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture_set_frame_texture
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "set_frame_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_set_frame_texture #-}

instance Method "set_frame_texture" GodotAnimatedTexture
           (Int -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_set_frame_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture_get_frame_texture
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "get_frame_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_get_frame_texture #-}

instance Method "get_frame_texture" GodotAnimatedTexture
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_get_frame_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture_set_frame_delay
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "set_frame_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_set_frame_delay #-}

instance Method "set_frame_delay" GodotAnimatedTexture
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_set_frame_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture_get_frame_delay
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "get_frame_delay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture_get_frame_delay #-}

instance Method "get_frame_delay" GodotAnimatedTexture
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture_get_frame_delay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimatedTexture__update_proxy
  = unsafePerformIO $
      withCString "AnimatedTexture" $
        \ clsNamePtr ->
          withCString "_update_proxy" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimatedTexture__update_proxy #-}

instance Method "_update_proxy" GodotAnimatedTexture (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimatedTexture__update_proxy
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTextureLayered = GodotTextureLayered GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotTextureLayered where
        type BaseClass GodotTextureLayered = GodotResource
        super = coerce
bindTextureLayered_set_flags
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "set_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_set_flags #-}

instance Method "set_flags" GodotTextureLayered (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_set_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_get_flags
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "get_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_get_flags #-}

instance Method "get_flags" GodotTextureLayered (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_get_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_get_format
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_get_format #-}

instance Method "get_format" GodotTextureLayered (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_get_format (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_get_width
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_get_width #-}

instance Method "get_width" GodotTextureLayered (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_get_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_get_height
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_get_height #-}

instance Method "get_height" GodotTextureLayered (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_get_depth
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "get_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_get_depth #-}

instance Method "get_depth" GodotTextureLayered (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_get_depth (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_create
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "create" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_create #-}

instance Method "create" GodotTextureLayered
           (Int -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_create (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_set_layer_data
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "set_layer_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_set_layer_data #-}

instance Method "set_layer_data" GodotTextureLayered
           (GodotImage -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_set_layer_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_get_layer_data
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "get_layer_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_get_layer_data #-}

instance Method "get_layer_data" GodotTextureLayered
           (Int -> IO GodotImage)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_get_layer_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered_set_data_partial
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "set_data_partial" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered_set_data_partial #-}

instance Method "set_data_partial" GodotTextureLayered
           (GodotImage -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered_set_data_partial
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered__set_data
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered__set_data #-}

instance Method "_set_data" GodotTextureLayered
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered__set_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindTextureLayered__get_data
  = unsafePerformIO $
      withCString "TextureLayered" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindTextureLayered__get_data #-}

instance Method "_get_data" GodotTextureLayered
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindTextureLayered__get_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTexture3D = GodotTexture3D GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotTexture3D where
        type BaseClass GodotTexture3D = GodotTextureLayered
        super = coerce

newtype GodotTextureArray = GodotTextureArray GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotTextureArray where
        type BaseClass GodotTextureArray = GodotTextureLayered
        super = coerce

newtype GodotAnimation = GodotAnimation GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotAnimation where
        type BaseClass GodotAnimation = GodotResource
        super = coerce
bindAnimation_add_track
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "add_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_add_track #-}

instance Method "add_track" GodotAnimation (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_add_track (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_remove_track
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "remove_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_remove_track #-}

instance Method "remove_track" GodotAnimation (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_remove_track (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_get_track_count
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "get_track_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_get_track_count #-}

instance Method "get_track_count" GodotAnimation (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_get_track_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_type
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_type #-}

instance Method "track_get_type" GodotAnimation (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_get_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_path
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_path #-}

instance Method "track_get_path" GodotAnimation
           (Int -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_get_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_set_path
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_set_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_set_path #-}

instance Method "track_set_path" GodotAnimation
           (Int -> GodotNodePath -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_set_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_find_track
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "find_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_find_track #-}

instance Method "find_track" GodotAnimation
           (GodotNodePath -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_find_track (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_move_up
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_move_up" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_move_up #-}

instance Method "track_move_up" GodotAnimation (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_move_up (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_move_down
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_move_down" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_move_down #-}

instance Method "track_move_down" GodotAnimation (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_move_down (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_swap
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_swap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_swap #-}

instance Method "track_swap" GodotAnimation (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_swap (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_set_imported
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_set_imported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_set_imported #-}

instance Method "track_set_imported" GodotAnimation
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_set_imported
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_is_imported
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_is_imported" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_is_imported #-}

instance Method "track_is_imported" GodotAnimation (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_is_imported (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_set_enabled
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_set_enabled #-}

instance Method "track_set_enabled" GodotAnimation
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_set_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_is_enabled
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_is_enabled #-}

instance Method "track_is_enabled" GodotAnimation (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_is_enabled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_transform_track_insert_key
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "transform_track_insert_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_transform_track_insert_key #-}

instance Method "transform_track_insert_key" GodotAnimation
           (Int ->
              Float -> GodotVector3 -> GodotQuat -> GodotVector3 -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_transform_track_insert_key
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_insert_key
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_insert_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_insert_key #-}

instance Method "track_insert_key" GodotAnimation
           (Int -> Float -> GodotVariant -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_insert_key (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_remove_key
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_remove_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_remove_key #-}

instance Method "track_remove_key" GodotAnimation
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_remove_key (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_remove_key_at_position
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_remove_key_at_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_remove_key_at_position #-}

instance Method "track_remove_key_at_position" GodotAnimation
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_remove_key_at_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_set_key_value
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_set_key_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_set_key_value #-}

instance Method "track_set_key_value" GodotAnimation
           (Int -> Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_set_key_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_set_key_transition
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_set_key_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_set_key_transition #-}

instance Method "track_set_key_transition" GodotAnimation
           (Int -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_set_key_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_key_transition
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_key_transition" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_key_transition #-}

instance Method "track_get_key_transition" GodotAnimation
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_get_key_transition
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_key_count
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_key_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_key_count #-}

instance Method "track_get_key_count" GodotAnimation
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_get_key_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_key_value
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_key_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_key_value #-}

instance Method "track_get_key_value" GodotAnimation
           (Int -> Int -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_get_key_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_key_time
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_key_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_key_time #-}

instance Method "track_get_key_time" GodotAnimation
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_get_key_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_find_key
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_find_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_find_key #-}

instance Method "track_find_key" GodotAnimation
           (Int -> Float -> Bool -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_find_key (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_set_interpolation_type
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_set_interpolation_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_set_interpolation_type #-}

instance Method "track_set_interpolation_type" GodotAnimation
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_set_interpolation_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_interpolation_type
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_interpolation_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_interpolation_type #-}

instance Method "track_get_interpolation_type" GodotAnimation
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_track_get_interpolation_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_set_interpolation_loop_wrap
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_set_interpolation_loop_wrap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_set_interpolation_loop_wrap #-}

instance Method "track_set_interpolation_loop_wrap" GodotAnimation
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_track_set_interpolation_loop_wrap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_track_get_interpolation_loop_wrap
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "track_get_interpolation_loop_wrap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_track_get_interpolation_loop_wrap #-}

instance Method "track_get_interpolation_loop_wrap" GodotAnimation
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_track_get_interpolation_loop_wrap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_transform_track_interpolate
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "transform_track_interpolate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_transform_track_interpolate #-}

instance Method "transform_track_interpolate" GodotAnimation
           (Int -> Float -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_transform_track_interpolate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_value_track_set_update_mode
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "value_track_set_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_value_track_set_update_mode #-}

instance Method "value_track_set_update_mode" GodotAnimation
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_value_track_set_update_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_value_track_get_update_mode
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "value_track_get_update_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_value_track_get_update_mode #-}

instance Method "value_track_get_update_mode" GodotAnimation
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_value_track_get_update_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_value_track_get_key_indices
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "value_track_get_key_indices" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_value_track_get_key_indices #-}

instance Method "value_track_get_key_indices" GodotAnimation
           (Int -> Float -> Float -> IO GodotPoolIntArray)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_value_track_get_key_indices
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_method_track_get_key_indices
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "method_track_get_key_indices" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_method_track_get_key_indices #-}

instance Method "method_track_get_key_indices" GodotAnimation
           (Int -> Float -> Float -> IO GodotPoolIntArray)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_method_track_get_key_indices
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_method_track_get_name
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "method_track_get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_method_track_get_name #-}

instance Method "method_track_get_name" GodotAnimation
           (Int -> Int -> IO GodotString)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_method_track_get_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_method_track_get_params
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "method_track_get_params" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_method_track_get_params #-}

instance Method "method_track_get_params" GodotAnimation
           (Int -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_method_track_get_params
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_insert_key
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_insert_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_insert_key #-}

instance Method "bezier_track_insert_key" GodotAnimation
           (Int -> Float -> Float -> GodotVector2 -> GodotVector2 -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_bezier_track_insert_key
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_set_key_value
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_set_key_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_set_key_value #-}

instance Method "bezier_track_set_key_value" GodotAnimation
           (Int -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_bezier_track_set_key_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_set_key_in_handle
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_set_key_in_handle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_set_key_in_handle #-}

instance Method "bezier_track_set_key_in_handle" GodotAnimation
           (Int -> Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_bezier_track_set_key_in_handle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_set_key_out_handle
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_set_key_out_handle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_set_key_out_handle #-}

instance Method "bezier_track_set_key_out_handle" GodotAnimation
           (Int -> Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_bezier_track_set_key_out_handle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_get_key_value
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_get_key_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_get_key_value #-}

instance Method "bezier_track_get_key_value" GodotAnimation
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_bezier_track_get_key_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_get_key_in_handle
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_get_key_in_handle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_get_key_in_handle #-}

instance Method "bezier_track_get_key_in_handle" GodotAnimation
           (Int -> Int -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_bezier_track_get_key_in_handle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_get_key_out_handle
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_get_key_out_handle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_get_key_out_handle #-}

instance Method "bezier_track_get_key_out_handle" GodotAnimation
           (Int -> Int -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_bezier_track_get_key_out_handle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_bezier_track_interpolate
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "bezier_track_interpolate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_bezier_track_interpolate #-}

instance Method "bezier_track_interpolate" GodotAnimation
           (Int -> Float -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_bezier_track_interpolate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_audio_track_insert_key
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "audio_track_insert_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_audio_track_insert_key #-}

instance Method "audio_track_insert_key" GodotAnimation
           (Int -> Float -> GodotResource -> Float -> Float -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_audio_track_insert_key
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_audio_track_set_key_stream
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "audio_track_set_key_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_audio_track_set_key_stream #-}

instance Method "audio_track_set_key_stream" GodotAnimation
           (Int -> Int -> GodotResource -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_audio_track_set_key_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_audio_track_set_key_start_offset
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "audio_track_set_key_start_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_audio_track_set_key_start_offset #-}

instance Method "audio_track_set_key_start_offset" GodotAnimation
           (Int -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_audio_track_set_key_start_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_audio_track_set_key_end_offset
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "audio_track_set_key_end_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_audio_track_set_key_end_offset #-}

instance Method "audio_track_set_key_end_offset" GodotAnimation
           (Int -> Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_audio_track_set_key_end_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_audio_track_get_key_stream
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "audio_track_get_key_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_audio_track_get_key_stream #-}

instance Method "audio_track_get_key_stream" GodotAnimation
           (Int -> Int -> IO GodotResource)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_audio_track_get_key_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_audio_track_get_key_start_offset
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "audio_track_get_key_start_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_audio_track_get_key_start_offset #-}

instance Method "audio_track_get_key_start_offset" GodotAnimation
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_audio_track_get_key_start_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_audio_track_get_key_end_offset
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "audio_track_get_key_end_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_audio_track_get_key_end_offset #-}

instance Method "audio_track_get_key_end_offset" GodotAnimation
           (Int -> Int -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_audio_track_get_key_end_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_animation_track_insert_key
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "animation_track_insert_key" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_animation_track_insert_key #-}

instance Method "animation_track_insert_key" GodotAnimation
           (Int -> Float -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_animation_track_insert_key
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_animation_track_set_key_animation
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "animation_track_set_key_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_animation_track_set_key_animation #-}

instance Method "animation_track_set_key_animation" GodotAnimation
           (Int -> Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_animation_track_set_key_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_animation_track_get_key_animation
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "animation_track_get_key_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_animation_track_get_key_animation #-}

instance Method "animation_track_get_key_animation" GodotAnimation
           (Int -> Int -> IO GodotString)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAnimation_animation_track_get_key_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_set_length
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "set_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_set_length #-}

instance Method "set_length" GodotAnimation (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_set_length (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_get_length
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "get_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_get_length #-}

instance Method "get_length" GodotAnimation (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_get_length (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_set_loop
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "set_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_set_loop #-}

instance Method "set_loop" GodotAnimation (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_set_loop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_has_loop
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "has_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_has_loop #-}

instance Method "has_loop" GodotAnimation (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_has_loop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_set_step
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "set_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_set_step #-}

instance Method "set_step" GodotAnimation (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_set_step (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_get_step
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "get_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_get_step #-}

instance Method "get_step" GodotAnimation (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_get_step (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_clear
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_clear #-}

instance Method "clear" GodotAnimation (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAnimation_copy_track
  = unsafePerformIO $
      withCString "Animation" $
        \ clsNamePtr ->
          withCString "copy_track" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAnimation_copy_track #-}

instance Method "copy_track" GodotAnimation
           (Int -> GodotAnimation -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAnimation_copy_track (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotFont = GodotFont GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotFont where
        type BaseClass GodotFont = GodotResource
        super = coerce
bindFont_draw
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_draw #-}

instance Method "draw" GodotFont
           (GodotRid ->
              GodotVector2 ->
                GodotString -> GodotColor -> Int -> GodotColor -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_draw (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_get_ascent
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "get_ascent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_get_ascent #-}

instance Method "get_ascent" GodotFont (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_get_ascent (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_get_descent
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "get_descent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_get_descent #-}

instance Method "get_descent" GodotFont (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_get_descent (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_get_height
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_get_height #-}

instance Method "get_height" GodotFont (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_get_height (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_is_distance_field_hint
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "is_distance_field_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_is_distance_field_hint #-}

instance Method "is_distance_field_hint" GodotFont (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_is_distance_field_hint (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_get_string_size
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "get_string_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_get_string_size #-}

instance Method "get_string_size" GodotFont
           (GodotString -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_get_string_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_has_outline
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "has_outline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_has_outline #-}

instance Method "has_outline" GodotFont (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_has_outline (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_draw_char
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "draw_char" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_draw_char #-}

instance Method "draw_char" GodotFont
           (GodotRid ->
              GodotVector2 -> Int -> Int -> GodotColor -> Bool -> IO Float)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_draw_char (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindFont_update_changes
  = unsafePerformIO $
      withCString "Font" $
        \ clsNamePtr ->
          withCString "update_changes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindFont_update_changes #-}

instance Method "update_changes" GodotFont (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindFont_update_changes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBitmapFont = GodotBitmapFont GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotBitmapFont where
        type BaseClass GodotBitmapFont = GodotFont
        super = coerce
bindBitmapFont_get_height
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_get_height #-}

instance Method "get_height" GodotBitmapFont (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_get_ascent
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "get_ascent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_get_ascent #-}

instance Method "get_ascent" GodotBitmapFont (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_get_ascent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_is_distance_field_hint
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "is_distance_field_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_is_distance_field_hint #-}

instance Method "is_distance_field_hint" GodotBitmapFont (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_is_distance_field_hint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_create_from_fnt
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "create_from_fnt" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_create_from_fnt #-}

instance Method "create_from_fnt" GodotBitmapFont
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_create_from_fnt (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_set_height
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_set_height #-}

instance Method "set_height" GodotBitmapFont (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_set_ascent
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "set_ascent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_set_ascent #-}

instance Method "set_ascent" GodotBitmapFont (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_set_ascent (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_add_kerning_pair
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "add_kerning_pair" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_add_kerning_pair #-}

instance Method "add_kerning_pair" GodotBitmapFont
           (Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_add_kerning_pair (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_get_kerning_pair
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "get_kerning_pair" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_get_kerning_pair #-}

instance Method "get_kerning_pair" GodotBitmapFont
           (Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_get_kerning_pair (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_add_texture
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "add_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_add_texture #-}

instance Method "add_texture" GodotBitmapFont
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_add_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_add_char
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "add_char" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_add_char #-}

instance Method "add_char" GodotBitmapFont
           (Int -> Int -> GodotRect2 -> GodotVector2 -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_add_char (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_get_texture_count
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "get_texture_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_get_texture_count #-}

instance Method "get_texture_count" GodotBitmapFont (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_get_texture_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_get_texture
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_get_texture #-}

instance Method "get_texture" GodotBitmapFont
           (Int -> IO GodotTexture)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_get_char_size
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "get_char_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_get_char_size #-}

instance Method "get_char_size" GodotBitmapFont
           (Int -> Int -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_get_char_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_set_distance_field_hint
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "set_distance_field_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_set_distance_field_hint #-}

instance Method "set_distance_field_hint" GodotBitmapFont
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_set_distance_field_hint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_clear
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_clear #-}

instance Method "clear" GodotBitmapFont (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont__set_chars
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "_set_chars" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont__set_chars #-}

instance Method "_set_chars" GodotBitmapFont
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont__set_chars (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont__get_chars
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "_get_chars" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont__get_chars #-}

instance Method "_get_chars" GodotBitmapFont (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont__get_chars (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont__set_kernings
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "_set_kernings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont__set_kernings #-}

instance Method "_set_kernings" GodotBitmapFont
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont__set_kernings (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont__get_kernings
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "_get_kernings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont__get_kernings #-}

instance Method "_get_kernings" GodotBitmapFont
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont__get_kernings (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont__set_textures
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "_set_textures" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont__set_textures #-}

instance Method "_set_textures" GodotBitmapFont
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont__set_textures (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont__get_textures
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "_get_textures" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont__get_textures #-}

instance Method "_get_textures" GodotBitmapFont (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont__get_textures (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_set_fallback
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "set_fallback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_set_fallback #-}

instance Method "set_fallback" GodotBitmapFont
           (GodotBitmapFont -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_set_fallback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindBitmapFont_get_fallback
  = unsafePerformIO $
      withCString "BitmapFont" $
        \ clsNamePtr ->
          withCString "get_fallback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindBitmapFont_get_fallback #-}

instance Method "get_fallback" GodotBitmapFont (IO GodotBitmapFont)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindBitmapFont_get_fallback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotTextFile = GodotTextFile GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotTextFile where
        type BaseClass GodotTextFile = GodotResource
        super = coerce

newtype GodotDynamicFontData = GodotDynamicFontData GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotDynamicFontData where
        type BaseClass GodotDynamicFontData = GodotResource
        super = coerce
bindDynamicFontData_set_font_path
  = unsafePerformIO $
      withCString "DynamicFontData" $
        \ clsNamePtr ->
          withCString "set_font_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFontData_set_font_path #-}

instance Method "set_font_path" GodotDynamicFontData
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFontData_set_font_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFontData_get_font_path
  = unsafePerformIO $
      withCString "DynamicFontData" $
        \ clsNamePtr ->
          withCString "get_font_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFontData_get_font_path #-}

instance Method "get_font_path" GodotDynamicFontData
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFontData_get_font_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFontData_set_hinting
  = unsafePerformIO $
      withCString "DynamicFontData" $
        \ clsNamePtr ->
          withCString "set_hinting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFontData_set_hinting #-}

instance Method "set_hinting" GodotDynamicFontData (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFontData_set_hinting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFontData_get_hinting
  = unsafePerformIO $
      withCString "DynamicFontData" $
        \ clsNamePtr ->
          withCString "get_hinting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFontData_get_hinting #-}

instance Method "get_hinting" GodotDynamicFontData (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFontData_get_hinting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotDynamicFont = GodotDynamicFont GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotDynamicFont where
        type BaseClass GodotDynamicFont = GodotFont
        super = coerce
bindDynamicFont_set_font_data
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_font_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_font_data #-}

instance Method "set_font_data" GodotDynamicFont
           (GodotDynamicFontData -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_font_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_font_data
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_font_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_font_data #-}

instance Method "get_font_data" GodotDynamicFont
           (IO GodotDynamicFontData)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_font_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_set_size
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_size #-}

instance Method "set_size" GodotDynamicFont (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_size
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_size #-}

instance Method "get_size" GodotDynamicFont (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_size (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_set_outline_size
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_outline_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_outline_size #-}

instance Method "set_outline_size" GodotDynamicFont (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_outline_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_outline_size
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_outline_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_outline_size #-}

instance Method "get_outline_size" GodotDynamicFont (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_outline_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_set_outline_color
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_outline_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_outline_color #-}

instance Method "set_outline_color" GodotDynamicFont
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_outline_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_outline_color
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_outline_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_outline_color #-}

instance Method "get_outline_color" GodotDynamicFont
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_outline_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_set_use_mipmaps
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_use_mipmaps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_use_mipmaps #-}

instance Method "set_use_mipmaps" GodotDynamicFont (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_use_mipmaps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_use_mipmaps
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_use_mipmaps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_use_mipmaps #-}

instance Method "get_use_mipmaps" GodotDynamicFont (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_use_mipmaps (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_set_use_filter
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_use_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_use_filter #-}

instance Method "set_use_filter" GodotDynamicFont (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_use_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_use_filter
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_use_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_use_filter #-}

instance Method "get_use_filter" GodotDynamicFont (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_use_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_set_spacing
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_spacing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_spacing #-}

instance Method "set_spacing" GodotDynamicFont
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_spacing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_spacing
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_spacing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_spacing #-}

instance Method "get_spacing" GodotDynamicFont (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_spacing (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_add_fallback
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "add_fallback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_add_fallback #-}

instance Method "add_fallback" GodotDynamicFont
           (GodotDynamicFontData -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_add_fallback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_set_fallback
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "set_fallback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_set_fallback #-}

instance Method "set_fallback" GodotDynamicFont
           (Int -> GodotDynamicFontData -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_set_fallback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_fallback
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_fallback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_fallback #-}

instance Method "get_fallback" GodotDynamicFont
           (Int -> IO GodotDynamicFontData)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_fallback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_remove_fallback
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "remove_fallback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_remove_fallback #-}

instance Method "remove_fallback" GodotDynamicFont (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_remove_fallback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindDynamicFont_get_fallback_count
  = unsafePerformIO $
      withCString "DynamicFont" $
        \ clsNamePtr ->
          withCString "get_fallback_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindDynamicFont_get_fallback_count #-}

instance Method "get_fallback_count" GodotDynamicFont (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindDynamicFont_get_fallback_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStyleBox = GodotStyleBox GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotStyleBox where
        type BaseClass GodotStyleBox = GodotResource
        super = coerce
bindStyleBox_test_mask
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "test_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_test_mask #-}

instance Method "test_mask" GodotStyleBox
           (GodotVector2 -> GodotRect2 -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_test_mask (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBox_set_default_margin
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "set_default_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_set_default_margin #-}

instance Method "set_default_margin" GodotStyleBox
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_set_default_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBox_get_default_margin
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "get_default_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_get_default_margin #-}

instance Method "get_default_margin" GodotStyleBox
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_get_default_margin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBox_get_margin
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "get_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_get_margin #-}

instance Method "get_margin" GodotStyleBox (Int -> IO Float) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_get_margin (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBox_get_minimum_size
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "get_minimum_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_get_minimum_size #-}

instance Method "get_minimum_size" GodotStyleBox (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_get_minimum_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBox_get_center_size
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "get_center_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_get_center_size #-}

instance Method "get_center_size" GodotStyleBox (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_get_center_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBox_get_offset
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_get_offset #-}

instance Method "get_offset" GodotStyleBox (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_get_offset (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBox_draw
  = unsafePerformIO $
      withCString "StyleBox" $
        \ clsNamePtr ->
          withCString "draw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBox_draw #-}

instance Method "draw" GodotStyleBox
           (GodotRid -> GodotRect2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBox_draw (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStyleBoxEmpty = GodotStyleBoxEmpty GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotStyleBoxEmpty where
        type BaseClass GodotStyleBoxEmpty = GodotStyleBox
        super = coerce

newtype GodotStyleBoxTexture = GodotStyleBoxTexture GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotStyleBoxTexture where
        type BaseClass GodotStyleBoxTexture = GodotStyleBox
        super = coerce
bindStyleBoxTexture_set_texture
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_texture #-}

instance Method "set_texture" GodotStyleBoxTexture
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_texture
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_texture #-}

instance Method "get_texture" GodotStyleBoxTexture
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_texture (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_normal_map
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_normal_map #-}

instance Method "set_normal_map" GodotStyleBoxTexture
           (GodotTexture -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_normal_map
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_normal_map
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_normal_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_normal_map #-}

instance Method "get_normal_map" GodotStyleBoxTexture
           (IO GodotTexture)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_normal_map
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_margin_size
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_margin_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_margin_size #-}

instance Method "set_margin_size" GodotStyleBoxTexture
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_margin_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_margin_size
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_margin_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_margin_size #-}

instance Method "get_margin_size" GodotStyleBoxTexture
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_margin_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_expand_margin_size
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_expand_margin_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_expand_margin_size #-}

instance Method "set_expand_margin_size" GodotStyleBoxTexture
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_expand_margin_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_expand_margin_all
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_expand_margin_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_expand_margin_all #-}

instance Method "set_expand_margin_all" GodotStyleBoxTexture
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_expand_margin_all
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_expand_margin_individual
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_expand_margin_individual" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_expand_margin_individual #-}

instance Method "set_expand_margin_individual" GodotStyleBoxTexture
           (Float -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStyleBoxTexture_set_expand_margin_individual
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_expand_margin_size
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_expand_margin_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_expand_margin_size #-}

instance Method "get_expand_margin_size" GodotStyleBoxTexture
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_expand_margin_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_region_rect
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_region_rect #-}

instance Method "set_region_rect" GodotStyleBoxTexture
           (GodotRect2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_region_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_region_rect
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_region_rect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_region_rect #-}

instance Method "get_region_rect" GodotStyleBoxTexture
           (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_region_rect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_draw_center
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_draw_center" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_draw_center #-}

instance Method "set_draw_center" GodotStyleBoxTexture
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_draw_center
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_is_draw_center_enabled
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "is_draw_center_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_is_draw_center_enabled #-}

instance Method "is_draw_center_enabled" GodotStyleBoxTexture
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_is_draw_center_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_modulate
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_modulate #-}

instance Method "set_modulate" GodotStyleBoxTexture
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_modulate
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_modulate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_modulate #-}

instance Method "get_modulate" GodotStyleBoxTexture (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_modulate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_h_axis_stretch_mode
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_h_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_h_axis_stretch_mode #-}

instance Method "set_h_axis_stretch_mode" GodotStyleBoxTexture
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_h_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_h_axis_stretch_mode
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_h_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_h_axis_stretch_mode #-}

instance Method "get_h_axis_stretch_mode" GodotStyleBoxTexture
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_h_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_set_v_axis_stretch_mode
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "set_v_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_set_v_axis_stretch_mode #-}

instance Method "set_v_axis_stretch_mode" GodotStyleBoxTexture
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_set_v_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxTexture_get_v_axis_stretch_mode
  = unsafePerformIO $
      withCString "StyleBoxTexture" $
        \ clsNamePtr ->
          withCString "get_v_axis_stretch_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxTexture_get_v_axis_stretch_mode #-}

instance Method "get_v_axis_stretch_mode" GodotStyleBoxTexture
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxTexture_get_v_axis_stretch_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStyleBoxFlat = GodotStyleBoxFlat GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotStyleBoxFlat where
        type BaseClass GodotStyleBoxFlat = GodotStyleBox
        super = coerce
bindStyleBoxFlat_set_bg_color
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_bg_color #-}

instance Method "set_bg_color" GodotStyleBoxFlat
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_bg_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_bg_color
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_bg_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_bg_color #-}

instance Method "get_bg_color" GodotStyleBoxFlat (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_bg_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_border_color
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_border_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_border_color #-}

instance Method "set_border_color" GodotStyleBoxFlat
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_border_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_border_color
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_border_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_border_color #-}

instance Method "get_border_color" GodotStyleBoxFlat
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_border_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_border_width_all
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_border_width_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_border_width_all #-}

instance Method "set_border_width_all" GodotStyleBoxFlat
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_border_width_all
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_border_width_min
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_border_width_min" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_border_width_min #-}

instance Method "get_border_width_min" GodotStyleBoxFlat (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_border_width_min
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_border_width
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_border_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_border_width #-}

instance Method "set_border_width" GodotStyleBoxFlat
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_border_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_border_width
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_border_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_border_width #-}

instance Method "get_border_width" GodotStyleBoxFlat
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_border_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_border_blend
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_border_blend" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_border_blend #-}

instance Method "set_border_blend" GodotStyleBoxFlat
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_border_blend
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_border_blend
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_border_blend" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_border_blend #-}

instance Method "get_border_blend" GodotStyleBoxFlat (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_border_blend
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_corner_radius_individual
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_corner_radius_individual" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_corner_radius_individual #-}

instance Method "set_corner_radius_individual" GodotStyleBoxFlat
           (Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStyleBoxFlat_set_corner_radius_individual
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_corner_radius_all
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_corner_radius_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_corner_radius_all #-}

instance Method "set_corner_radius_all" GodotStyleBoxFlat
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_corner_radius_all
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_corner_radius
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_corner_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_corner_radius #-}

instance Method "set_corner_radius" GodotStyleBoxFlat
           (Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_corner_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_corner_radius
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_corner_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_corner_radius #-}

instance Method "get_corner_radius" GodotStyleBoxFlat
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_corner_radius
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_expand_margin
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_expand_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_expand_margin #-}

instance Method "set_expand_margin" GodotStyleBoxFlat
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_expand_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_expand_margin_all
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_expand_margin_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_expand_margin_all #-}

instance Method "set_expand_margin_all" GodotStyleBoxFlat
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_expand_margin_all
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_expand_margin_individual
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_expand_margin_individual" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_expand_margin_individual #-}

instance Method "set_expand_margin_individual" GodotStyleBoxFlat
           (Float -> Float -> Float -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindStyleBoxFlat_set_expand_margin_individual
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_expand_margin
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_expand_margin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_expand_margin #-}

instance Method "get_expand_margin" GodotStyleBoxFlat
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_expand_margin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_draw_center
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_draw_center" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_draw_center #-}

instance Method "set_draw_center" GodotStyleBoxFlat (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_draw_center
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_is_draw_center_enabled
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "is_draw_center_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_is_draw_center_enabled #-}

instance Method "is_draw_center_enabled" GodotStyleBoxFlat
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_is_draw_center_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_shadow_color
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_shadow_color #-}

instance Method "set_shadow_color" GodotStyleBoxFlat
           (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_shadow_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_shadow_color
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_shadow_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_shadow_color #-}

instance Method "get_shadow_color" GodotStyleBoxFlat
           (IO GodotColor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_shadow_color
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_shadow_size
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_shadow_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_shadow_size #-}

instance Method "set_shadow_size" GodotStyleBoxFlat (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_shadow_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_shadow_size
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_shadow_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_shadow_size #-}

instance Method "get_shadow_size" GodotStyleBoxFlat (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_shadow_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_anti_aliased
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_anti_aliased" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_anti_aliased #-}

instance Method "set_anti_aliased" GodotStyleBoxFlat
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_anti_aliased
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_is_anti_aliased
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "is_anti_aliased" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_is_anti_aliased #-}

instance Method "is_anti_aliased" GodotStyleBoxFlat (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_is_anti_aliased
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_aa_size
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_aa_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_aa_size #-}

instance Method "set_aa_size" GodotStyleBoxFlat (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_aa_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_aa_size
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_aa_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_aa_size #-}

instance Method "get_aa_size" GodotStyleBoxFlat (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_aa_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_set_corner_detail
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "set_corner_detail" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_set_corner_detail #-}

instance Method "set_corner_detail" GodotStyleBoxFlat
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_set_corner_detail
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxFlat_get_corner_detail
  = unsafePerformIO $
      withCString "StyleBoxFlat" $
        \ clsNamePtr ->
          withCString "get_corner_detail" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxFlat_get_corner_detail #-}

instance Method "get_corner_detail" GodotStyleBoxFlat (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxFlat_get_corner_detail
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotStyleBoxLine = GodotStyleBoxLine GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotStyleBoxLine where
        type BaseClass GodotStyleBoxLine = GodotStyleBox
        super = coerce
bindStyleBoxLine_set_color
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "set_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_set_color #-}

instance Method "set_color" GodotStyleBoxLine (GodotColor -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_set_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_get_color
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "get_color" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_get_color #-}

instance Method "get_color" GodotStyleBoxLine (IO GodotColor) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_get_color (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_set_thickness
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "set_thickness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_set_thickness #-}

instance Method "set_thickness" GodotStyleBoxLine (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_set_thickness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_get_thickness
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "get_thickness" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_get_thickness #-}

instance Method "get_thickness" GodotStyleBoxLine (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_get_thickness (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_set_grow_begin
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "set_grow_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_set_grow_begin #-}

instance Method "set_grow_begin" GodotStyleBoxLine (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_set_grow_begin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_get_grow_begin
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "get_grow_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_get_grow_begin #-}

instance Method "get_grow_begin" GodotStyleBoxLine (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_get_grow_begin (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_set_grow_end
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "set_grow_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_set_grow_end #-}

instance Method "set_grow_end" GodotStyleBoxLine (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_set_grow_end (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_get_grow_end
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "get_grow_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_get_grow_end #-}

instance Method "get_grow_end" GodotStyleBoxLine (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_get_grow_end (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_set_vertical
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "set_vertical" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_set_vertical #-}

instance Method "set_vertical" GodotStyleBoxLine (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_set_vertical (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindStyleBoxLine_is_vertical
  = unsafePerformIO $
      withCString "StyleBoxLine" $
        \ clsNamePtr ->
          withCString "is_vertical" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindStyleBoxLine_is_vertical #-}

instance Method "is_vertical" GodotStyleBoxLine (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindStyleBoxLine_is_vertical (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPolygonPathFinder = GodotPolygonPathFinder GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotPolygonPathFinder where
        type BaseClass GodotPolygonPathFinder = GodotResource
        super = coerce
bindPolygonPathFinder_setup
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "setup" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_setup #-}

instance Method "setup" GodotPolygonPathFinder
           (GodotPoolVector2Array -> GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_setup (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder_find_path
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "find_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_find_path #-}

instance Method "find_path" GodotPolygonPathFinder
           (GodotVector2 -> GodotVector2 -> IO GodotPoolVector2Array)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_find_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder_get_intersections
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "get_intersections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_get_intersections #-}

instance Method "get_intersections" GodotPolygonPathFinder
           (GodotVector2 -> GodotVector2 -> IO GodotPoolVector2Array)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_get_intersections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder_get_closest_point
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "get_closest_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_get_closest_point #-}

instance Method "get_closest_point" GodotPolygonPathFinder
           (GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_get_closest_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder_is_point_inside
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "is_point_inside" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_is_point_inside #-}

instance Method "is_point_inside" GodotPolygonPathFinder
           (GodotVector2 -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_is_point_inside
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder_set_point_penalty
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "set_point_penalty" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_set_point_penalty #-}

instance Method "set_point_penalty" GodotPolygonPathFinder
           (Int -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_set_point_penalty
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder_get_point_penalty
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "get_point_penalty" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_get_point_penalty #-}

instance Method "get_point_penalty" GodotPolygonPathFinder
           (Int -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_get_point_penalty
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder_get_bounds
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "get_bounds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder_get_bounds #-}

instance Method "get_bounds" GodotPolygonPathFinder (IO GodotRect2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder_get_bounds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder__set_data
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder__set_data #-}

instance Method "_set_data" GodotPolygonPathFinder
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder__set_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPolygonPathFinder__get_data
  = unsafePerformIO $
      withCString "PolygonPathFinder" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPolygonPathFinder__get_data #-}

instance Method "_get_data" GodotPolygonPathFinder
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPolygonPathFinder__get_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioStreamPlayer = GodotAudioStreamPlayer GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamPlayer where
        type BaseClass GodotAudioStreamPlayer = GodotNode
        super = coerce
bindAudioStreamPlayer_set_stream
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "set_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_set_stream #-}

instance Method "set_stream" GodotAudioStreamPlayer
           (GodotAudioStream -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_set_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_get_stream
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "get_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_get_stream #-}

instance Method "get_stream" GodotAudioStreamPlayer
           (IO GodotAudioStream)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_get_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_set_volume_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "set_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_set_volume_db #-}

instance Method "set_volume_db" GodotAudioStreamPlayer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_set_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_get_volume_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "get_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_get_volume_db #-}

instance Method "get_volume_db" GodotAudioStreamPlayer (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_get_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_set_pitch_scale
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "set_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_set_pitch_scale #-}

instance Method "set_pitch_scale" GodotAudioStreamPlayer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_set_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_get_pitch_scale
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "get_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_get_pitch_scale #-}

instance Method "get_pitch_scale" GodotAudioStreamPlayer (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_get_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_play
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_play #-}

instance Method "play" GodotAudioStreamPlayer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_play (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_seek
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_seek #-}

instance Method "seek" GodotAudioStreamPlayer (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_seek (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_stop
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_stop #-}

instance Method "stop" GodotAudioStreamPlayer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_stop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_is_playing
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_is_playing #-}

instance Method "is_playing" GodotAudioStreamPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_is_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_get_playback_position
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "get_playback_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_get_playback_position #-}

instance Method "get_playback_position" GodotAudioStreamPlayer
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_get_playback_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_set_bus
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "set_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_set_bus #-}

instance Method "set_bus" GodotAudioStreamPlayer
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_set_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_get_bus
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "get_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_get_bus #-}

instance Method "get_bus" GodotAudioStreamPlayer (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_get_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_set_autoplay
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "set_autoplay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_set_autoplay #-}

instance Method "set_autoplay" GodotAudioStreamPlayer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_set_autoplay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_is_autoplay_enabled
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "is_autoplay_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_is_autoplay_enabled #-}

instance Method "is_autoplay_enabled" GodotAudioStreamPlayer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_is_autoplay_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_set_mix_target
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "set_mix_target" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_set_mix_target #-}

instance Method "set_mix_target" GodotAudioStreamPlayer
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_set_mix_target
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_get_mix_target
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "get_mix_target" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_get_mix_target #-}

instance Method "get_mix_target" GodotAudioStreamPlayer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_get_mix_target
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer__set_playing
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "_set_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer__set_playing #-}

instance Method "_set_playing" GodotAudioStreamPlayer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer__set_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer__is_active
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer__is_active #-}

instance Method "_is_active" GodotAudioStreamPlayer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer__is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer__bus_layout_changed
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "_bus_layout_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer__bus_layout_changed #-}

instance Method "_bus_layout_changed" GodotAudioStreamPlayer
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer__bus_layout_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_set_stream_paused
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "set_stream_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_set_stream_paused #-}

instance Method "set_stream_paused" GodotAudioStreamPlayer
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_set_stream_paused
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer_get_stream_paused
  = unsafePerformIO $
      withCString "AudioStreamPlayer" $
        \ clsNamePtr ->
          withCString "get_stream_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer_get_stream_paused #-}

instance Method "get_stream_paused" GodotAudioStreamPlayer
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer_get_stream_paused
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioStreamPlayer2D = GodotAudioStreamPlayer2D GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamPlayer2D where
        type BaseClass GodotAudioStreamPlayer2D = GodotNode2D
        super = coerce
bindAudioStreamPlayer2D_set_stream
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_stream #-}

instance Method "set_stream" GodotAudioStreamPlayer2D
           (GodotAudioStream -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_stream
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_stream #-}

instance Method "get_stream" GodotAudioStreamPlayer2D
           (IO GodotAudioStream)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_volume_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_volume_db #-}

instance Method "set_volume_db" GodotAudioStreamPlayer2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_volume_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_volume_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_volume_db #-}

instance Method "get_volume_db" GodotAudioStreamPlayer2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_volume_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_pitch_scale
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_pitch_scale #-}

instance Method "set_pitch_scale" GodotAudioStreamPlayer2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_pitch_scale
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_pitch_scale #-}

instance Method "get_pitch_scale" GodotAudioStreamPlayer2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_play
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_play #-}

instance Method "play" GodotAudioStreamPlayer2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_play (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_seek
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_seek #-}

instance Method "seek" GodotAudioStreamPlayer2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_seek (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_stop
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_stop #-}

instance Method "stop" GodotAudioStreamPlayer2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_stop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_is_playing
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_is_playing #-}

instance Method "is_playing" GodotAudioStreamPlayer2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_is_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_playback_position
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_playback_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_playback_position #-}

instance Method "get_playback_position" GodotAudioStreamPlayer2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer2D_get_playback_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_bus
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_bus #-}

instance Method "set_bus" GodotAudioStreamPlayer2D
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_bus
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_bus #-}

instance Method "get_bus" GodotAudioStreamPlayer2D (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_autoplay
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_autoplay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_autoplay #-}

instance Method "set_autoplay" GodotAudioStreamPlayer2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_autoplay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_is_autoplay_enabled
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "is_autoplay_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_is_autoplay_enabled #-}

instance Method "is_autoplay_enabled" GodotAudioStreamPlayer2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_is_autoplay_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D__set_playing
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "_set_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D__set_playing #-}

instance Method "_set_playing" GodotAudioStreamPlayer2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D__set_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D__is_active
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D__is_active #-}

instance Method "_is_active" GodotAudioStreamPlayer2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D__is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_max_distance
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_max_distance #-}

instance Method "set_max_distance" GodotAudioStreamPlayer2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_max_distance
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_max_distance #-}

instance Method "get_max_distance" GodotAudioStreamPlayer2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_attenuation
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_attenuation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_attenuation #-}

instance Method "set_attenuation" GodotAudioStreamPlayer2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_attenuation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_attenuation
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_attenuation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_attenuation #-}

instance Method "get_attenuation" GodotAudioStreamPlayer2D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_attenuation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_area_mask
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_area_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_area_mask #-}

instance Method "set_area_mask" GodotAudioStreamPlayer2D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_area_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_area_mask
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_area_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_area_mask #-}

instance Method "get_area_mask" GodotAudioStreamPlayer2D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_area_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_set_stream_paused
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "set_stream_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_set_stream_paused #-}

instance Method "set_stream_paused" GodotAudioStreamPlayer2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_set_stream_paused
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D_get_stream_paused
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "get_stream_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D_get_stream_paused #-}

instance Method "get_stream_paused" GodotAudioStreamPlayer2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D_get_stream_paused
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer2D__bus_layout_changed
  = unsafePerformIO $
      withCString "AudioStreamPlayer2D" $
        \ clsNamePtr ->
          withCString "_bus_layout_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer2D__bus_layout_changed #-}

instance Method "_bus_layout_changed" GodotAudioStreamPlayer2D
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer2D__bus_layout_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioStreamPlayer3D = GodotAudioStreamPlayer3D GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamPlayer3D where
        type BaseClass GodotAudioStreamPlayer3D = GodotSpatial
        super = coerce
bindAudioStreamPlayer3D_set_stream
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_stream #-}

instance Method "set_stream" GodotAudioStreamPlayer3D
           (GodotAudioStream -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_stream
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_stream" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_stream #-}

instance Method "get_stream" GodotAudioStreamPlayer3D
           (IO GodotAudioStream)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_stream
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_unit_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_unit_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_unit_db #-}

instance Method "set_unit_db" GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_unit_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_unit_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_unit_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_unit_db #-}

instance Method "get_unit_db" GodotAudioStreamPlayer3D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_unit_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_unit_size
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_unit_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_unit_size #-}

instance Method "set_unit_size" GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_unit_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_unit_size
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_unit_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_unit_size #-}

instance Method "get_unit_size" GodotAudioStreamPlayer3D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_unit_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_max_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_max_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_max_db #-}

instance Method "set_max_db" GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_max_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_max_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_max_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_max_db #-}

instance Method "get_max_db" GodotAudioStreamPlayer3D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_max_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_pitch_scale
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_pitch_scale #-}

instance Method "set_pitch_scale" GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_pitch_scale
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_pitch_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_pitch_scale #-}

instance Method "get_pitch_scale" GodotAudioStreamPlayer3D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_pitch_scale
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_play
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_play #-}

instance Method "play" GodotAudioStreamPlayer3D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_play (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_seek
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "seek" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_seek #-}

instance Method "seek" GodotAudioStreamPlayer3D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_seek (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_stop
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_stop #-}

instance Method "stop" GodotAudioStreamPlayer3D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_stop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_is_playing
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "is_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_is_playing #-}

instance Method "is_playing" GodotAudioStreamPlayer3D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_is_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_playback_position
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_playback_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_playback_position #-}

instance Method "get_playback_position" GodotAudioStreamPlayer3D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_get_playback_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_bus
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_bus #-}

instance Method "set_bus" GodotAudioStreamPlayer3D
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_bus
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_bus" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_bus #-}

instance Method "get_bus" GodotAudioStreamPlayer3D (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_bus (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_autoplay
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_autoplay" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_autoplay #-}

instance Method "set_autoplay" GodotAudioStreamPlayer3D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_autoplay
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_is_autoplay_enabled
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "is_autoplay_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_is_autoplay_enabled #-}

instance Method "is_autoplay_enabled" GodotAudioStreamPlayer3D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_is_autoplay_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D__set_playing
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "_set_playing" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D__set_playing #-}

instance Method "_set_playing" GodotAudioStreamPlayer3D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D__set_playing
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D__is_active
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "_is_active" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D__is_active #-}

instance Method "_is_active" GodotAudioStreamPlayer3D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D__is_active
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_max_distance
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_max_distance #-}

instance Method "set_max_distance" GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_max_distance
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_max_distance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_max_distance #-}

instance Method "get_max_distance" GodotAudioStreamPlayer3D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_max_distance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_area_mask
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_area_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_area_mask #-}

instance Method "set_area_mask" GodotAudioStreamPlayer3D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_area_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_area_mask
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_area_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_area_mask #-}

instance Method "get_area_mask" GodotAudioStreamPlayer3D (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_area_mask
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_emission_angle
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_emission_angle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_emission_angle #-}

instance Method "set_emission_angle" GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_emission_angle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_emission_angle
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_emission_angle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_emission_angle #-}

instance Method "get_emission_angle" GodotAudioStreamPlayer3D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_emission_angle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_emission_angle_enabled
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_emission_angle_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_emission_angle_enabled #-}

instance Method "set_emission_angle_enabled"
           GodotAudioStreamPlayer3D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_set_emission_angle_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_is_emission_angle_enabled
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "is_emission_angle_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_is_emission_angle_enabled #-}

instance Method "is_emission_angle_enabled"
           GodotAudioStreamPlayer3D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_is_emission_angle_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_emission_angle_filter_attenuation_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_emission_angle_filter_attenuation_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_emission_angle_filter_attenuation_db
             #-}

instance Method "set_emission_angle_filter_attenuation_db"
           GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_set_emission_angle_filter_attenuation_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_emission_angle_filter_attenuation_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_emission_angle_filter_attenuation_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_emission_angle_filter_attenuation_db
             #-}

instance Method "get_emission_angle_filter_attenuation_db"
           GodotAudioStreamPlayer3D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_get_emission_angle_filter_attenuation_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_attenuation_filter_cutoff_hz
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_attenuation_filter_cutoff_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_attenuation_filter_cutoff_hz
             #-}

instance Method "set_attenuation_filter_cutoff_hz"
           GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_set_attenuation_filter_cutoff_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_attenuation_filter_cutoff_hz
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_attenuation_filter_cutoff_hz" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_attenuation_filter_cutoff_hz
             #-}

instance Method "get_attenuation_filter_cutoff_hz"
           GodotAudioStreamPlayer3D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_get_attenuation_filter_cutoff_hz
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_attenuation_filter_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_attenuation_filter_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_attenuation_filter_db #-}

instance Method "set_attenuation_filter_db"
           GodotAudioStreamPlayer3D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_set_attenuation_filter_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_attenuation_filter_db
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_attenuation_filter_db" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_attenuation_filter_db #-}

instance Method "get_attenuation_filter_db"
           GodotAudioStreamPlayer3D
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_get_attenuation_filter_db
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_attenuation_model
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_attenuation_model" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_attenuation_model #-}

instance Method "set_attenuation_model" GodotAudioStreamPlayer3D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_set_attenuation_model
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_attenuation_model
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_attenuation_model" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_attenuation_model #-}

instance Method "get_attenuation_model" GodotAudioStreamPlayer3D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_get_attenuation_model
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_out_of_range_mode
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_out_of_range_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_out_of_range_mode #-}

instance Method "set_out_of_range_mode" GodotAudioStreamPlayer3D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_set_out_of_range_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_out_of_range_mode
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_out_of_range_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_out_of_range_mode #-}

instance Method "get_out_of_range_mode" GodotAudioStreamPlayer3D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindAudioStreamPlayer3D_get_out_of_range_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_doppler_tracking
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_doppler_tracking" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_doppler_tracking #-}

instance Method "set_doppler_tracking" GodotAudioStreamPlayer3D
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_doppler_tracking
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_doppler_tracking
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_doppler_tracking" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_doppler_tracking #-}

instance Method "get_doppler_tracking" GodotAudioStreamPlayer3D
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_doppler_tracking
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_set_stream_paused
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "set_stream_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_set_stream_paused #-}

instance Method "set_stream_paused" GodotAudioStreamPlayer3D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_set_stream_paused
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D_get_stream_paused
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "get_stream_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D_get_stream_paused #-}

instance Method "get_stream_paused" GodotAudioStreamPlayer3D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D_get_stream_paused
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamPlayer3D__bus_layout_changed
  = unsafePerformIO $
      withCString "AudioStreamPlayer3D" $
        \ clsNamePtr ->
          withCString "_bus_layout_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamPlayer3D__bus_layout_changed #-}

instance Method "_bus_layout_changed" GodotAudioStreamPlayer3D
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamPlayer3D__bus_layout_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAudioStreamSample = GodotAudioStreamSample GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamSample where
        type BaseClass GodotAudioStreamSample = GodotAudioStream
        super = coerce
bindAudioStreamSample_set_data
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_set_data #-}

instance Method "set_data" GodotAudioStreamSample
           (GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_set_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_get_data
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_get_data #-}

instance Method "get_data" GodotAudioStreamSample
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_get_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_set_format
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "set_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_set_format #-}

instance Method "set_format" GodotAudioStreamSample (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_set_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_get_format
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "get_format" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_get_format #-}

instance Method "get_format" GodotAudioStreamSample (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_get_format
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_set_loop_mode
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "set_loop_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_set_loop_mode #-}

instance Method "set_loop_mode" GodotAudioStreamSample
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_set_loop_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_get_loop_mode
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "get_loop_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_get_loop_mode #-}

instance Method "get_loop_mode" GodotAudioStreamSample (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_get_loop_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_set_loop_begin
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "set_loop_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_set_loop_begin #-}

instance Method "set_loop_begin" GodotAudioStreamSample
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_set_loop_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_get_loop_begin
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "get_loop_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_get_loop_begin #-}

instance Method "get_loop_begin" GodotAudioStreamSample (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_get_loop_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_set_loop_end
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "set_loop_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_set_loop_end #-}

instance Method "set_loop_end" GodotAudioStreamSample
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_set_loop_end
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_get_loop_end
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "get_loop_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_get_loop_end #-}

instance Method "get_loop_end" GodotAudioStreamSample (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_get_loop_end
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_set_mix_rate
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "set_mix_rate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_set_mix_rate #-}

instance Method "set_mix_rate" GodotAudioStreamSample
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_set_mix_rate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_get_mix_rate
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "get_mix_rate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_get_mix_rate #-}

instance Method "get_mix_rate" GodotAudioStreamSample (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_get_mix_rate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_set_stereo
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "set_stereo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_set_stereo #-}

instance Method "set_stereo" GodotAudioStreamSample (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_set_stereo
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_is_stereo
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "is_stereo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_is_stereo #-}

instance Method "is_stereo" GodotAudioStreamSample (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_is_stereo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamSample_save_to_wav
  = unsafePerformIO $
      withCString "AudioStreamSample" $
        \ clsNamePtr ->
          withCString "save_to_wav" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamSample_save_to_wav #-}

instance Method "save_to_wav" GodotAudioStreamSample
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamSample_save_to_wav
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotLineShape2D = GodotLineShape2D GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotLineShape2D where
        type BaseClass GodotLineShape2D = GodotShape2D
        super = coerce
bindLineShape2D_set_normal
  = unsafePerformIO $
      withCString "LineShape2D" $
        \ clsNamePtr ->
          withCString "set_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineShape2D_set_normal #-}

instance Method "set_normal" GodotLineShape2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineShape2D_set_normal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineShape2D_get_normal
  = unsafePerformIO $
      withCString "LineShape2D" $
        \ clsNamePtr ->
          withCString "get_normal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineShape2D_get_normal #-}

instance Method "get_normal" GodotLineShape2D (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineShape2D_get_normal (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineShape2D_set_d
  = unsafePerformIO $
      withCString "LineShape2D" $
        \ clsNamePtr ->
          withCString "set_d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineShape2D_set_d #-}

instance Method "set_d" GodotLineShape2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineShape2D_set_d (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindLineShape2D_get_d
  = unsafePerformIO $
      withCString "LineShape2D" $
        \ clsNamePtr ->
          withCString "get_d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindLineShape2D_get_d #-}

instance Method "get_d" GodotLineShape2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindLineShape2D_get_d (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSegmentShape2D = GodotSegmentShape2D GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotSegmentShape2D where
        type BaseClass GodotSegmentShape2D = GodotShape2D
        super = coerce
bindSegmentShape2D_set_a
  = unsafePerformIO $
      withCString "SegmentShape2D" $
        \ clsNamePtr ->
          withCString "set_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSegmentShape2D_set_a #-}

instance Method "set_a" GodotSegmentShape2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSegmentShape2D_set_a (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSegmentShape2D_get_a
  = unsafePerformIO $
      withCString "SegmentShape2D" $
        \ clsNamePtr ->
          withCString "get_a" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSegmentShape2D_get_a #-}

instance Method "get_a" GodotSegmentShape2D (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSegmentShape2D_get_a (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSegmentShape2D_set_b
  = unsafePerformIO $
      withCString "SegmentShape2D" $
        \ clsNamePtr ->
          withCString "set_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSegmentShape2D_set_b #-}

instance Method "set_b" GodotSegmentShape2D (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSegmentShape2D_set_b (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSegmentShape2D_get_b
  = unsafePerformIO $
      withCString "SegmentShape2D" $
        \ clsNamePtr ->
          withCString "get_b" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSegmentShape2D_get_b #-}

instance Method "get_b" GodotSegmentShape2D (IO GodotVector2) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSegmentShape2D_get_b (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRayShape2D = GodotRayShape2D GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotRayShape2D where
        type BaseClass GodotRayShape2D = GodotShape2D
        super = coerce
bindRayShape2D_set_length
  = unsafePerformIO $
      withCString "RayShape2D" $
        \ clsNamePtr ->
          withCString "set_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape2D_set_length #-}

instance Method "set_length" GodotRayShape2D (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape2D_set_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayShape2D_get_length
  = unsafePerformIO $
      withCString "RayShape2D" $
        \ clsNamePtr ->
          withCString "get_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape2D_get_length #-}

instance Method "get_length" GodotRayShape2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape2D_get_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayShape2D_set_slips_on_slope
  = unsafePerformIO $
      withCString "RayShape2D" $
        \ clsNamePtr ->
          withCString "set_slips_on_slope" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape2D_set_slips_on_slope #-}

instance Method "set_slips_on_slope" GodotRayShape2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape2D_set_slips_on_slope
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRayShape2D_get_slips_on_slope
  = unsafePerformIO $
      withCString "RayShape2D" $
        \ clsNamePtr ->
          withCString "get_slips_on_slope" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRayShape2D_get_slips_on_slope #-}

instance Method "get_slips_on_slope" GodotRayShape2D (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRayShape2D_get_slips_on_slope
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCircleShape2D = GodotCircleShape2D GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotCircleShape2D where
        type BaseClass GodotCircleShape2D = GodotShape2D
        super = coerce
bindCircleShape2D_set_radius
  = unsafePerformIO $
      withCString "CircleShape2D" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCircleShape2D_set_radius #-}

instance Method "set_radius" GodotCircleShape2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCircleShape2D_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCircleShape2D_get_radius
  = unsafePerformIO $
      withCString "CircleShape2D" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCircleShape2D_get_radius #-}

instance Method "get_radius" GodotCircleShape2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCircleShape2D_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRectangleShape2D = GodotRectangleShape2D GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotRectangleShape2D where
        type BaseClass GodotRectangleShape2D = GodotShape2D
        super = coerce
bindRectangleShape2D_set_extents
  = unsafePerformIO $
      withCString "RectangleShape2D" $
        \ clsNamePtr ->
          withCString "set_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRectangleShape2D_set_extents #-}

instance Method "set_extents" GodotRectangleShape2D
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRectangleShape2D_set_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRectangleShape2D_get_extents
  = unsafePerformIO $
      withCString "RectangleShape2D" $
        \ clsNamePtr ->
          withCString "get_extents" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRectangleShape2D_get_extents #-}

instance Method "get_extents" GodotRectangleShape2D
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRectangleShape2D_get_extents
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCapsuleShape2D = GodotCapsuleShape2D GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotCapsuleShape2D where
        type BaseClass GodotCapsuleShape2D = GodotShape2D
        super = coerce
bindCapsuleShape2D_set_radius
  = unsafePerformIO $
      withCString "CapsuleShape2D" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape2D_set_radius #-}

instance Method "set_radius" GodotCapsuleShape2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape2D_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleShape2D_get_radius
  = unsafePerformIO $
      withCString "CapsuleShape2D" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape2D_get_radius #-}

instance Method "get_radius" GodotCapsuleShape2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape2D_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleShape2D_set_height
  = unsafePerformIO $
      withCString "CapsuleShape2D" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape2D_set_height #-}

instance Method "set_height" GodotCapsuleShape2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape2D_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCapsuleShape2D_get_height
  = unsafePerformIO $
      withCString "CapsuleShape2D" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCapsuleShape2D_get_height #-}

instance Method "get_height" GodotCapsuleShape2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCapsuleShape2D_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotConvexPolygonShape2D = GodotConvexPolygonShape2D GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotConvexPolygonShape2D where
        type BaseClass GodotConvexPolygonShape2D = GodotShape2D
        super = coerce
bindConvexPolygonShape2D_set_point_cloud
  = unsafePerformIO $
      withCString "ConvexPolygonShape2D" $
        \ clsNamePtr ->
          withCString "set_point_cloud" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConvexPolygonShape2D_set_point_cloud #-}

instance Method "set_point_cloud" GodotConvexPolygonShape2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConvexPolygonShape2D_set_point_cloud
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConvexPolygonShape2D_set_points
  = unsafePerformIO $
      withCString "ConvexPolygonShape2D" $
        \ clsNamePtr ->
          withCString "set_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConvexPolygonShape2D_set_points #-}

instance Method "set_points" GodotConvexPolygonShape2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConvexPolygonShape2D_set_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConvexPolygonShape2D_get_points
  = unsafePerformIO $
      withCString "ConvexPolygonShape2D" $
        \ clsNamePtr ->
          withCString "get_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConvexPolygonShape2D_get_points #-}

instance Method "get_points" GodotConvexPolygonShape2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConvexPolygonShape2D_get_points
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotConcavePolygonShape2D = GodotConcavePolygonShape2D GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotConcavePolygonShape2D where
        type BaseClass GodotConcavePolygonShape2D = GodotShape2D
        super = coerce
bindConcavePolygonShape2D_set_segments
  = unsafePerformIO $
      withCString "ConcavePolygonShape2D" $
        \ clsNamePtr ->
          withCString "set_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConcavePolygonShape2D_set_segments #-}

instance Method "set_segments" GodotConcavePolygonShape2D
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConcavePolygonShape2D_set_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindConcavePolygonShape2D_get_segments
  = unsafePerformIO $
      withCString "ConcavePolygonShape2D" $
        \ clsNamePtr ->
          withCString "get_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindConcavePolygonShape2D_get_segments #-}

instance Method "get_segments" GodotConcavePolygonShape2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindConcavePolygonShape2D_get_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCurve2D = GodotCurve2D GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotCurve2D where
        type BaseClass GodotCurve2D = GodotResource
        super = coerce
bindCurve2D_get_point_count
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_point_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_point_count #-}

instance Method "get_point_count" GodotCurve2D (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_point_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_add_point
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "add_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_add_point #-}

instance Method "add_point" GodotCurve2D
           (GodotVector2 -> GodotVector2 -> GodotVector2 -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_add_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_set_point_position
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "set_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_set_point_position #-}

instance Method "set_point_position" GodotCurve2D
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_set_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_point_position
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_point_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_point_position #-}

instance Method "get_point_position" GodotCurve2D
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_point_position (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_set_point_in
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "set_point_in" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_set_point_in #-}

instance Method "set_point_in" GodotCurve2D
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_set_point_in (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_point_in
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_point_in" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_point_in #-}

instance Method "get_point_in" GodotCurve2D
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_point_in (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_set_point_out
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "set_point_out" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_set_point_out #-}

instance Method "set_point_out" GodotCurve2D
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_set_point_out (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_point_out
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_point_out" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_point_out #-}

instance Method "get_point_out" GodotCurve2D
           (Int -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_point_out (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_remove_point
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "remove_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_remove_point #-}

instance Method "remove_point" GodotCurve2D (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_remove_point (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_clear_points
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "clear_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_clear_points #-}

instance Method "clear_points" GodotCurve2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_clear_points (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_interpolate
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "interpolate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_interpolate #-}

instance Method "interpolate" GodotCurve2D
           (Int -> Float -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_interpolate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_interpolatef
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "interpolatef" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_interpolatef #-}

instance Method "interpolatef" GodotCurve2D
           (Float -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_interpolatef (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_set_bake_interval
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "set_bake_interval" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_set_bake_interval #-}

instance Method "set_bake_interval" GodotCurve2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_set_bake_interval (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_bake_interval
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_bake_interval" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_bake_interval #-}

instance Method "get_bake_interval" GodotCurve2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_bake_interval (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_baked_length
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_baked_length" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_baked_length #-}

instance Method "get_baked_length" GodotCurve2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_baked_length (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_interpolate_baked
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "interpolate_baked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_interpolate_baked #-}

instance Method "interpolate_baked" GodotCurve2D
           (Float -> Bool -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_interpolate_baked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_baked_points
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_baked_points" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_baked_points #-}

instance Method "get_baked_points" GodotCurve2D
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_baked_points (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_closest_point
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_closest_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_closest_point #-}

instance Method "get_closest_point" GodotCurve2D
           (GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_closest_point (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_get_closest_offset
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "get_closest_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_get_closest_offset #-}

instance Method "get_closest_offset" GodotCurve2D
           (GodotVector2 -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_get_closest_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D_tessellate
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "tessellate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D_tessellate #-}

instance Method "tessellate" GodotCurve2D
           (Int -> Float -> IO GodotPoolVector2Array)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D_tessellate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D__get_data
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D__get_data #-}

instance Method "_get_data" GodotCurve2D (IO GodotDictionary) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D__get_data (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCurve2D__set_data
  = unsafePerformIO $
      withCString "Curve2D" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCurve2D__set_data #-}

instance Method "_set_data" GodotCurve2D (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCurve2D__set_data (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPath2D = GodotPath2D GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotPath2D where
        type BaseClass GodotPath2D = GodotNode2D
        super = coerce
bindPath2D_set_curve
  = unsafePerformIO $
      withCString "Path2D" $
        \ clsNamePtr ->
          withCString "set_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPath2D_set_curve #-}

instance Method "set_curve" GodotPath2D (GodotCurve2D -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPath2D_set_curve (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPath2D_get_curve
  = unsafePerformIO $
      withCString "Path2D" $
        \ clsNamePtr ->
          withCString "get_curve" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPath2D_get_curve #-}

instance Method "get_curve" GodotPath2D (IO GodotCurve2D) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPath2D_get_curve (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPath2D__curve_changed
  = unsafePerformIO $
      withCString "Path2D" $
        \ clsNamePtr ->
          withCString "_curve_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPath2D__curve_changed #-}

instance Method "_curve_changed" GodotPath2D (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPath2D__curve_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPathFollow2D = GodotPathFollow2D GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotPathFollow2D where
        type BaseClass GodotPathFollow2D = GodotNode2D
        super = coerce
bindPathFollow2D_set_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_offset #-}

instance Method "set_offset" GodotPathFollow2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_get_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "get_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_get_offset #-}

instance Method "get_offset" GodotPathFollow2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_get_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_set_h_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_h_offset #-}

instance Method "set_h_offset" GodotPathFollow2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_h_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_get_h_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "get_h_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_get_h_offset #-}

instance Method "get_h_offset" GodotPathFollow2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_get_h_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_set_v_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_v_offset #-}

instance Method "set_v_offset" GodotPathFollow2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_v_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_get_v_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "get_v_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_get_v_offset #-}

instance Method "get_v_offset" GodotPathFollow2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_get_v_offset (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_set_unit_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_unit_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_unit_offset #-}

instance Method "set_unit_offset" GodotPathFollow2D
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_unit_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_get_unit_offset
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "get_unit_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_get_unit_offset #-}

instance Method "get_unit_offset" GodotPathFollow2D (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_get_unit_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_set_rotate
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_rotate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_rotate #-}

instance Method "set_rotate" GodotPathFollow2D (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_rotate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_is_rotating
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "is_rotating" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_is_rotating #-}

instance Method "is_rotating" GodotPathFollow2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_is_rotating (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_set_cubic_interpolation
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_cubic_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_cubic_interpolation #-}

instance Method "set_cubic_interpolation" GodotPathFollow2D
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_cubic_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_get_cubic_interpolation
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "get_cubic_interpolation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_get_cubic_interpolation #-}

instance Method "get_cubic_interpolation" GodotPathFollow2D
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_get_cubic_interpolation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_set_loop
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_loop #-}

instance Method "set_loop" GodotPathFollow2D (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_loop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_has_loop
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "has_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_has_loop #-}

instance Method "has_loop" GodotPathFollow2D (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_has_loop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_set_lookahead
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "set_lookahead" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_set_lookahead #-}

instance Method "set_lookahead" GodotPathFollow2D (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_set_lookahead (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPathFollow2D_get_lookahead
  = unsafePerformIO $
      withCString "PathFollow2D" $
        \ clsNamePtr ->
          withCString "get_lookahead" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPathFollow2D_get_lookahead #-}

instance Method "get_lookahead" GodotPathFollow2D (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPathFollow2D_get_lookahead (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNavigation2D = GodotNavigation2D GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotNavigation2D where
        type BaseClass GodotNavigation2D = GodotNode2D
        super = coerce
bindNavigation2D_navpoly_add
  = unsafePerformIO $
      withCString "Navigation2D" $
        \ clsNamePtr ->
          withCString "navpoly_add" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation2D_navpoly_add #-}

instance Method "navpoly_add" GodotNavigation2D
           (GodotNavigationPolygon ->
              GodotTransform2d -> GodotObject -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation2D_navpoly_add (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation2D_navpoly_set_transform
  = unsafePerformIO $
      withCString "Navigation2D" $
        \ clsNamePtr ->
          withCString "navpoly_set_transform" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation2D_navpoly_set_transform #-}

instance Method "navpoly_set_transform" GodotNavigation2D
           (Int -> GodotTransform2d -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation2D_navpoly_set_transform
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation2D_navpoly_remove
  = unsafePerformIO $
      withCString "Navigation2D" $
        \ clsNamePtr ->
          withCString "navpoly_remove" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation2D_navpoly_remove #-}

instance Method "navpoly_remove" GodotNavigation2D (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation2D_navpoly_remove (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation2D_get_simple_path
  = unsafePerformIO $
      withCString "Navigation2D" $
        \ clsNamePtr ->
          withCString "get_simple_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation2D_get_simple_path #-}

instance Method "get_simple_path" GodotNavigation2D
           (GodotVector2 -> GodotVector2 -> Bool -> IO GodotPoolVector2Array)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation2D_get_simple_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation2D_get_closest_point
  = unsafePerformIO $
      withCString "Navigation2D" $
        \ clsNamePtr ->
          withCString "get_closest_point" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation2D_get_closest_point #-}

instance Method "get_closest_point" GodotNavigation2D
           (GodotVector2 -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation2D_get_closest_point
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigation2D_get_closest_point_owner
  = unsafePerformIO $
      withCString "Navigation2D" $
        \ clsNamePtr ->
          withCString "get_closest_point_owner" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigation2D_get_closest_point_owner #-}

instance Method "get_closest_point_owner" GodotNavigation2D
           (GodotVector2 -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigation2D_get_closest_point_owner
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNavigationPolygon = GodotNavigationPolygon GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotNavigationPolygon where
        type BaseClass GodotNavigationPolygon = GodotResource
        super = coerce
bindNavigationPolygon_set_vertices
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "set_vertices" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_set_vertices #-}

instance Method "set_vertices" GodotNavigationPolygon
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_set_vertices
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_get_vertices
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "get_vertices" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_get_vertices #-}

instance Method "get_vertices" GodotNavigationPolygon
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_get_vertices
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_add_polygon
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "add_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_add_polygon #-}

instance Method "add_polygon" GodotNavigationPolygon
           (GodotPoolIntArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_add_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_get_polygon_count
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "get_polygon_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_get_polygon_count #-}

instance Method "get_polygon_count" GodotNavigationPolygon (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_get_polygon_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_get_polygon
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "get_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_get_polygon #-}

instance Method "get_polygon" GodotNavigationPolygon
           (Int -> IO GodotPoolIntArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_get_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_clear_polygons
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "clear_polygons" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_clear_polygons #-}

instance Method "clear_polygons" GodotNavigationPolygon (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_clear_polygons
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_add_outline
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "add_outline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_add_outline #-}

instance Method "add_outline" GodotNavigationPolygon
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_add_outline
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_add_outline_at_index
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "add_outline_at_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_add_outline_at_index #-}

instance Method "add_outline_at_index" GodotNavigationPolygon
           (GodotPoolVector2Array -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_add_outline_at_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_get_outline_count
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "get_outline_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_get_outline_count #-}

instance Method "get_outline_count" GodotNavigationPolygon (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_get_outline_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_set_outline
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "set_outline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_set_outline #-}

instance Method "set_outline" GodotNavigationPolygon
           (Int -> GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_set_outline
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_get_outline
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "get_outline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_get_outline #-}

instance Method "get_outline" GodotNavigationPolygon
           (Int -> IO GodotPoolVector2Array)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_get_outline
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_remove_outline
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "remove_outline" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_remove_outline #-}

instance Method "remove_outline" GodotNavigationPolygon
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_remove_outline
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_clear_outlines
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "clear_outlines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_clear_outlines #-}

instance Method "clear_outlines" GodotNavigationPolygon (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon_clear_outlines
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon_make_polygons_from_outlines
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "make_polygons_from_outlines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon_make_polygons_from_outlines #-}

instance Method "make_polygons_from_outlines"
           GodotNavigationPolygon
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationPolygon_make_polygons_from_outlines
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon__set_polygons
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "_set_polygons" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon__set_polygons #-}

instance Method "_set_polygons" GodotNavigationPolygon
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon__set_polygons
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon__get_polygons
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "_get_polygons" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon__get_polygons #-}

instance Method "_get_polygons" GodotNavigationPolygon
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon__get_polygons
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon__set_outlines
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "_set_outlines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon__set_outlines #-}

instance Method "_set_outlines" GodotNavigationPolygon
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon__set_outlines
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygon__get_outlines
  = unsafePerformIO $
      withCString "NavigationPolygon" $
        \ clsNamePtr ->
          withCString "_get_outlines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygon__get_outlines #-}

instance Method "_get_outlines" GodotNavigationPolygon
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygon__get_outlines
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNavigationPolygonInstance = GodotNavigationPolygonInstance GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotNavigationPolygonInstance where
        type BaseClass GodotNavigationPolygonInstance = GodotNode2D
        super = coerce
bindNavigationPolygonInstance_set_navigation_polygon
  = unsafePerformIO $
      withCString "NavigationPolygonInstance" $
        \ clsNamePtr ->
          withCString "set_navigation_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygonInstance_set_navigation_polygon
             #-}

instance Method "set_navigation_polygon"
           GodotNavigationPolygonInstance
           (GodotNavigationPolygon -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationPolygonInstance_set_navigation_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygonInstance_get_navigation_polygon
  = unsafePerformIO $
      withCString "NavigationPolygonInstance" $
        \ clsNamePtr ->
          withCString "get_navigation_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygonInstance_get_navigation_polygon
             #-}

instance Method "get_navigation_polygon"
           GodotNavigationPolygonInstance
           (IO GodotNavigationPolygon)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationPolygonInstance_get_navigation_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygonInstance_set_enabled
  = unsafePerformIO $
      withCString "NavigationPolygonInstance" $
        \ clsNamePtr ->
          withCString "set_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygonInstance_set_enabled #-}

instance Method "set_enabled" GodotNavigationPolygonInstance
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygonInstance_set_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygonInstance_is_enabled
  = unsafePerformIO $
      withCString "NavigationPolygonInstance" $
        \ clsNamePtr ->
          withCString "is_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygonInstance_is_enabled #-}

instance Method "is_enabled" GodotNavigationPolygonInstance
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNavigationPolygonInstance_is_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNavigationPolygonInstance__navpoly_changed
  = unsafePerformIO $
      withCString "NavigationPolygonInstance" $
        \ clsNamePtr ->
          withCString "_navpoly_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNavigationPolygonInstance__navpoly_changed #-}

instance Method "_navpoly_changed" GodotNavigationPolygonInstance
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNavigationPolygonInstance__navpoly_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSceneState = GodotSceneState GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotSceneState where
        type BaseClass GodotSceneState = GodotReference
        super = coerce
bindSceneState_get_node_count
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_count #-}

instance Method "get_node_count" GodotSceneState (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_type
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_type #-}

instance Method "get_node_type" GodotSceneState
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_name
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_name #-}

instance Method "get_node_name" GodotSceneState
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_path
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_path #-}

instance Method "get_node_path" GodotSceneState
           (Int -> Bool -> IO GodotNodePath)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_path (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_owner_path
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_owner_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_owner_path #-}

instance Method "get_node_owner_path" GodotSceneState
           (Int -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_owner_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_is_node_instance_placeholder
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "is_node_instance_placeholder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_is_node_instance_placeholder #-}

instance Method "is_node_instance_placeholder" GodotSceneState
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_is_node_instance_placeholder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_instance_placeholder
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_instance_placeholder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_instance_placeholder #-}

instance Method "get_node_instance_placeholder" GodotSceneState
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_instance_placeholder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_instance
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_instance #-}

instance Method "get_node_instance" GodotSceneState
           (Int -> IO GodotPackedScene)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_instance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_groups
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_groups" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_groups #-}

instance Method "get_node_groups" GodotSceneState
           (Int -> IO GodotPoolStringArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_groups (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_index
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_index #-}

instance Method "get_node_index" GodotSceneState (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_index (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_property_count
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_property_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_property_count #-}

instance Method "get_node_property_count" GodotSceneState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_property_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_property_name
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_property_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_property_name #-}

instance Method "get_node_property_name" GodotSceneState
           (Int -> Int -> IO GodotString)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_property_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_node_property_value
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_node_property_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_node_property_value #-}

instance Method "get_node_property_value" GodotSceneState
           (Int -> Int -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_node_property_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_connection_count
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_connection_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_connection_count #-}

instance Method "get_connection_count" GodotSceneState (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_connection_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_connection_source
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_connection_source" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_connection_source #-}

instance Method "get_connection_source" GodotSceneState
           (Int -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_connection_source
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_connection_signal
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_connection_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_connection_signal #-}

instance Method "get_connection_signal" GodotSceneState
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_connection_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_connection_target
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_connection_target" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_connection_target #-}

instance Method "get_connection_target" GodotSceneState
           (Int -> IO GodotNodePath)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_connection_target
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_connection_method
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_connection_method" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_connection_method #-}

instance Method "get_connection_method" GodotSceneState
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_connection_method
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_connection_flags
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_connection_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_connection_flags #-}

instance Method "get_connection_flags" GodotSceneState
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_connection_flags
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneState_get_connection_binds
  = unsafePerformIO $
      withCString "SceneState" $
        \ clsNamePtr ->
          withCString "get_connection_binds" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneState_get_connection_binds #-}

instance Method "get_connection_binds" GodotSceneState
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneState_get_connection_binds
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPackedScene = GodotPackedScene GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotPackedScene where
        type BaseClass GodotPackedScene = GodotResource
        super = coerce
bindPackedScene_pack
  = unsafePerformIO $
      withCString "PackedScene" $
        \ clsNamePtr ->
          withCString "pack" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedScene_pack #-}

instance Method "pack" GodotPackedScene (GodotObject -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedScene_pack (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedScene_instance
  = unsafePerformIO $
      withCString "PackedScene" $
        \ clsNamePtr ->
          withCString "instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedScene_instance #-}

instance Method "instance" GodotPackedScene (Int -> IO GodotNode)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedScene_instance (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedScene_can_instance
  = unsafePerformIO $
      withCString "PackedScene" $
        \ clsNamePtr ->
          withCString "can_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedScene_can_instance #-}

instance Method "can_instance" GodotPackedScene (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedScene_can_instance (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedScene__set_bundled_scene
  = unsafePerformIO $
      withCString "PackedScene" $
        \ clsNamePtr ->
          withCString "_set_bundled_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedScene__set_bundled_scene #-}

instance Method "_set_bundled_scene" GodotPackedScene
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedScene__set_bundled_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedScene__get_bundled_scene
  = unsafePerformIO $
      withCString "PackedScene" $
        \ clsNamePtr ->
          withCString "_get_bundled_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedScene__get_bundled_scene #-}

instance Method "_get_bundled_scene" GodotPackedScene
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedScene__get_bundled_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindPackedScene_get_state
  = unsafePerformIO $
      withCString "PackedScene" $
        \ clsNamePtr ->
          withCString "get_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindPackedScene_get_state #-}

instance Method "get_state" GodotPackedScene (IO GodotSceneState)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindPackedScene_get_state (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSceneTree = GodotSceneTree GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotSceneTree where
        type BaseClass GodotSceneTree = GodotMainLoop
        super = coerce
bindSceneTree_get_root
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_root #-}

instance Method "get_root" GodotSceneTree (IO GodotViewport) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_root (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_has_group
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "has_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_has_group #-}

instance Method "has_group" GodotSceneTree (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_has_group (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_auto_accept_quit
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_auto_accept_quit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_auto_accept_quit #-}

instance Method "set_auto_accept_quit" GodotSceneTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_auto_accept_quit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_quit_on_go_back
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_quit_on_go_back" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_quit_on_go_back #-}

instance Method "set_quit_on_go_back" GodotSceneTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_quit_on_go_back
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_debug_collisions_hint
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_debug_collisions_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_debug_collisions_hint #-}

instance Method "set_debug_collisions_hint" GodotSceneTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_debug_collisions_hint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_debugging_collisions_hint
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_debugging_collisions_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_debugging_collisions_hint #-}

instance Method "is_debugging_collisions_hint" GodotSceneTree
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_is_debugging_collisions_hint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_debug_navigation_hint
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_debug_navigation_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_debug_navigation_hint #-}

instance Method "set_debug_navigation_hint" GodotSceneTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_debug_navigation_hint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_debugging_navigation_hint
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_debugging_navigation_hint" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_debugging_navigation_hint #-}

instance Method "is_debugging_navigation_hint" GodotSceneTree
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_is_debugging_navigation_hint
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_edited_scene_root
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_edited_scene_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_edited_scene_root #-}

instance Method "set_edited_scene_root" GodotSceneTree
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_edited_scene_root
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_edited_scene_root
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_edited_scene_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_edited_scene_root #-}

instance Method "get_edited_scene_root" GodotSceneTree
           (IO GodotNode)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_edited_scene_root
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_pause
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_pause" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_pause #-}

instance Method "set_pause" GodotSceneTree (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_pause (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_paused
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_paused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_paused #-}

instance Method "is_paused" GodotSceneTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_is_paused (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_input_as_handled
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_input_as_handled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_input_as_handled #-}

instance Method "set_input_as_handled" GodotSceneTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_input_as_handled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_input_handled
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_input_handled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_input_handled #-}

instance Method "is_input_handled" GodotSceneTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_is_input_handled (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_create_timer
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "create_timer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_create_timer #-}

instance Method "create_timer" GodotSceneTree
           (Float -> Bool -> IO GodotSceneTreeTimer)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_create_timer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_node_count
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_node_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_node_count #-}

instance Method "get_node_count" GodotSceneTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_node_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_frame
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_frame" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_frame #-}

instance Method "get_frame" GodotSceneTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_frame (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_quit
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "quit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_quit #-}

instance Method "quit" GodotSceneTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_quit (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_screen_stretch
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_screen_stretch" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_screen_stretch #-}

instance Method "set_screen_stretch" GodotSceneTree
           (Int -> Int -> GodotVector2 -> Float -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_screen_stretch
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_queue_delete
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "queue_delete" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_queue_delete #-}

instance Method "queue_delete" GodotSceneTree
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_queue_delete (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_notify_group_flags
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "notify_group_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_notify_group_flags #-}

instance Method "notify_group_flags" GodotSceneTree
           (Int -> GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_notify_group_flags
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_group_flags
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_group_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_group_flags #-}

instance Method "set_group_flags" GodotSceneTree
           (Int -> GodotString -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_group_flags (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_notify_group
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "notify_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_notify_group #-}

instance Method "notify_group" GodotSceneTree
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_notify_group (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_group
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_group #-}

instance Method "set_group" GodotSceneTree
           (GodotString -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_group (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_nodes_in_group
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_nodes_in_group" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_nodes_in_group #-}

instance Method "get_nodes_in_group" GodotSceneTree
           (GodotString -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_nodes_in_group
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_current_scene
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_current_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_current_scene #-}

instance Method "set_current_scene" GodotSceneTree
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_current_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_current_scene
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_current_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_current_scene #-}

instance Method "get_current_scene" GodotSceneTree (IO GodotNode)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_current_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_change_scene
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "change_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_change_scene #-}

instance Method "change_scene" GodotSceneTree
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_change_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_change_scene_to
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "change_scene_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_change_scene_to #-}

instance Method "change_scene_to" GodotSceneTree
           (GodotPackedScene -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_change_scene_to (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_reload_current_scene
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "reload_current_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_reload_current_scene #-}

instance Method "reload_current_scene" GodotSceneTree (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_reload_current_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree__change_scene
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "_change_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree__change_scene #-}

instance Method "_change_scene" GodotSceneTree
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree__change_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_multiplayer
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_multiplayer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_multiplayer #-}

instance Method "set_multiplayer" GodotSceneTree
           (GodotMultiplayerAPI -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_multiplayer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_multiplayer
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_multiplayer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_multiplayer #-}

instance Method "get_multiplayer" GodotSceneTree
           (IO GodotMultiplayerAPI)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_multiplayer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_multiplayer_poll_enabled
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_multiplayer_poll_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_multiplayer_poll_enabled #-}

instance Method "set_multiplayer_poll_enabled" GodotSceneTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_multiplayer_poll_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_multiplayer_poll_enabled
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_multiplayer_poll_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_multiplayer_poll_enabled #-}

instance Method "is_multiplayer_poll_enabled" GodotSceneTree
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_is_multiplayer_poll_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_network_peer
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_network_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_network_peer #-}

instance Method "set_network_peer" GodotSceneTree
           (GodotNetworkedMultiplayerPeer -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_network_peer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_network_peer
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_network_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_network_peer #-}

instance Method "get_network_peer" GodotSceneTree
           (IO GodotNetworkedMultiplayerPeer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_network_peer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_network_server
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_network_server" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_network_server #-}

instance Method "is_network_server" GodotSceneTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_is_network_server (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_has_network_peer
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "has_network_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_has_network_peer #-}

instance Method "has_network_peer" GodotSceneTree (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_has_network_peer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_network_connected_peers
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_network_connected_peers" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_network_connected_peers #-}

instance Method "get_network_connected_peers" GodotSceneTree
           (IO GodotPoolIntArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_network_connected_peers
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_network_unique_id
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_network_unique_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_network_unique_id #-}

instance Method "get_network_unique_id" GodotSceneTree (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_network_unique_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_get_rpc_sender_id
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "get_rpc_sender_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_get_rpc_sender_id #-}

instance Method "get_rpc_sender_id" GodotSceneTree (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_get_rpc_sender_id (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_refuse_new_network_connections
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_refuse_new_network_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_refuse_new_network_connections #-}

instance Method "set_refuse_new_network_connections" GodotSceneTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSceneTree_set_refuse_new_network_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_refusing_new_network_connections
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_refusing_new_network_connections" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_refusing_new_network_connections #-}

instance Method "is_refusing_new_network_connections"
           GodotSceneTree
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindSceneTree_is_refusing_new_network_connections
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree__network_peer_connected
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "_network_peer_connected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree__network_peer_connected #-}

instance Method "_network_peer_connected" GodotSceneTree
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree__network_peer_connected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree__network_peer_disconnected
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "_network_peer_disconnected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree__network_peer_disconnected #-}

instance Method "_network_peer_disconnected" GodotSceneTree
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree__network_peer_disconnected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree__connected_to_server
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "_connected_to_server" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree__connected_to_server #-}

instance Method "_connected_to_server" GodotSceneTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree__connected_to_server
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree__connection_failed
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "_connection_failed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree__connection_failed #-}

instance Method "_connection_failed" GodotSceneTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree__connection_failed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree__server_disconnected
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "_server_disconnected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree__server_disconnected #-}

instance Method "_server_disconnected" GodotSceneTree (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree__server_disconnected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_set_use_font_oversampling
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "set_use_font_oversampling" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_set_use_font_oversampling #-}

instance Method "set_use_font_oversampling" GodotSceneTree
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_set_use_font_oversampling
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTree_is_using_font_oversampling
  = unsafePerformIO $
      withCString "SceneTree" $
        \ clsNamePtr ->
          withCString "is_using_font_oversampling" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTree_is_using_font_oversampling #-}

instance Method "is_using_font_oversampling" GodotSceneTree
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTree_is_using_font_oversampling
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotSceneTreeTimer = GodotSceneTreeTimer GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotSceneTreeTimer where
        type BaseClass GodotSceneTreeTimer = GodotReference
        super = coerce
bindSceneTreeTimer_set_time_left
  = unsafePerformIO $
      withCString "SceneTreeTimer" $
        \ clsNamePtr ->
          withCString "set_time_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTreeTimer_set_time_left #-}

instance Method "set_time_left" GodotSceneTreeTimer
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTreeTimer_set_time_left
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindSceneTreeTimer_get_time_left
  = unsafePerformIO $
      withCString "SceneTreeTimer" $
        \ clsNamePtr ->
          withCString "get_time_left" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindSceneTreeTimer_get_time_left #-}

instance Method "get_time_left" GodotSceneTreeTimer (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindSceneTreeTimer_get_time_left
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorPlugin = GodotEditorPlugin GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotEditorPlugin where
        type BaseClass GodotEditorPlugin = GodotNode
        super = coerce
bindEditorPlugin_forward_canvas_gui_input
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "forward_canvas_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_forward_canvas_gui_input #-}

instance Method "forward_canvas_gui_input" GodotEditorPlugin
           (GodotInputEvent -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_forward_canvas_gui_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_forward_canvas_draw_over_viewport
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "forward_canvas_draw_over_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_forward_canvas_draw_over_viewport #-}

instance Method "forward_canvas_draw_over_viewport"
           GodotEditorPlugin
           (GodotControl -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorPlugin_forward_canvas_draw_over_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_forward_canvas_force_draw_over_viewport
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "forward_canvas_force_draw_over_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_forward_canvas_force_draw_over_viewport
             #-}

instance Method "forward_canvas_force_draw_over_viewport"
           GodotEditorPlugin
           (GodotControl -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorPlugin_forward_canvas_force_draw_over_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_forward_spatial_gui_input
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "forward_spatial_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_forward_spatial_gui_input #-}

instance Method "forward_spatial_gui_input" GodotEditorPlugin
           (GodotCamera -> GodotInputEvent -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_forward_spatial_gui_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_plugin_name
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_plugin_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_plugin_name #-}

instance Method "get_plugin_name" GodotEditorPlugin
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_plugin_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_plugin_icon
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_plugin_icon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_plugin_icon #-}

instance Method "get_plugin_icon" GodotEditorPlugin
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_plugin_icon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_has_main_screen
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "has_main_screen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_has_main_screen #-}

instance Method "has_main_screen" GodotEditorPlugin (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_has_main_screen
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_make_visible
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "make_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_make_visible #-}

instance Method "make_visible" GodotEditorPlugin (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_make_visible (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_edit
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "edit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_edit #-}

instance Method "edit" GodotEditorPlugin (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_edit (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_handles
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "handles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_handles #-}

instance Method "handles" GodotEditorPlugin
           (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_handles (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_state
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_state #-}

instance Method "get_state" GodotEditorPlugin (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_state (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_set_state
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "set_state" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_set_state #-}

instance Method "set_state" GodotEditorPlugin
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_set_state (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_clear
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_clear #-}

instance Method "clear" GodotEditorPlugin (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_clear (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_save_external_data
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "save_external_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_save_external_data #-}

instance Method "save_external_data" GodotEditorPlugin (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_save_external_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_apply_changes
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "apply_changes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_apply_changes #-}

instance Method "apply_changes" GodotEditorPlugin (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_apply_changes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_breakpoints
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_breakpoints" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_breakpoints #-}

instance Method "get_breakpoints" GodotEditorPlugin
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_breakpoints
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_set_window_layout
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "set_window_layout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_set_window_layout #-}

instance Method "set_window_layout" GodotEditorPlugin
           (GodotConfigFile -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_set_window_layout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_window_layout
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_window_layout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_window_layout #-}

instance Method "get_window_layout" GodotEditorPlugin
           (GodotConfigFile -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_window_layout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_build
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "build" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_build #-}

instance Method "build" GodotEditorPlugin (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_build (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_control_to_container
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_control_to_container" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_control_to_container #-}

instance Method "add_control_to_container" GodotEditorPlugin
           (Int -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_control_to_container
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_control_to_bottom_panel
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_control_to_bottom_panel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_control_to_bottom_panel #-}

instance Method "add_control_to_bottom_panel" GodotEditorPlugin
           (GodotObject -> GodotString -> IO GodotToolButton)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_control_to_bottom_panel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_control_to_dock
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_control_to_dock" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_control_to_dock #-}

instance Method "add_control_to_dock" GodotEditorPlugin
           (Int -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_control_to_dock
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_control_from_docks
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_control_from_docks" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_control_from_docks #-}

instance Method "remove_control_from_docks" GodotEditorPlugin
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_control_from_docks
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_control_from_bottom_panel
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_control_from_bottom_panel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_control_from_bottom_panel #-}

instance Method "remove_control_from_bottom_panel"
           GodotEditorPlugin
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorPlugin_remove_control_from_bottom_panel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_control_from_container
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_control_from_container" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_control_from_container #-}

instance Method "remove_control_from_container" GodotEditorPlugin
           (Int -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorPlugin_remove_control_from_container
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_tool_menu_item
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_tool_menu_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_tool_menu_item #-}

instance Method "add_tool_menu_item" GodotEditorPlugin
           (GodotString ->
              GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_tool_menu_item
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_tool_submenu_item
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_tool_submenu_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_tool_submenu_item #-}

instance Method "add_tool_submenu_item" GodotEditorPlugin
           (GodotString -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_tool_submenu_item
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_tool_menu_item
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_tool_menu_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_tool_menu_item #-}

instance Method "remove_tool_menu_item" GodotEditorPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_tool_menu_item
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_custom_type
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_custom_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_custom_type #-}

instance Method "add_custom_type" GodotEditorPlugin
           (GodotString ->
              GodotString -> GodotScript -> GodotTexture -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_custom_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_custom_type
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_custom_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_custom_type #-}

instance Method "remove_custom_type" GodotEditorPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_custom_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_autoload_singleton
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_autoload_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_autoload_singleton #-}

instance Method "add_autoload_singleton" GodotEditorPlugin
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_autoload_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_autoload_singleton
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_autoload_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_autoload_singleton #-}

instance Method "remove_autoload_singleton" GodotEditorPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_autoload_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_update_overlays
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "update_overlays" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_update_overlays #-}

instance Method "update_overlays" GodotEditorPlugin (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_update_overlays
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_make_bottom_panel_item_visible
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "make_bottom_panel_item_visible" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_make_bottom_panel_item_visible #-}

instance Method "make_bottom_panel_item_visible" GodotEditorPlugin
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorPlugin_make_bottom_panel_item_visible
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_hide_bottom_panel
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "hide_bottom_panel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_hide_bottom_panel #-}

instance Method "hide_bottom_panel" GodotEditorPlugin (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_hide_bottom_panel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_undo_redo
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_undo_redo" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_undo_redo #-}

instance Method "get_undo_redo" GodotEditorPlugin
           (IO GodotUndoRedo)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_undo_redo (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_queue_save_layout
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "queue_save_layout" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_queue_save_layout #-}

instance Method "queue_save_layout" GodotEditorPlugin (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_queue_save_layout
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_import_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_import_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_import_plugin #-}

instance Method "add_import_plugin" GodotEditorPlugin
           (GodotEditorImportPlugin -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_import_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_import_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_import_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_import_plugin #-}

instance Method "remove_import_plugin" GodotEditorPlugin
           (GodotEditorImportPlugin -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_import_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_scene_import_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_scene_import_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_scene_import_plugin #-}

instance Method "add_scene_import_plugin" GodotEditorPlugin
           (GodotEditorSceneImporter -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_scene_import_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_scene_import_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_scene_import_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_scene_import_plugin #-}

instance Method "remove_scene_import_plugin" GodotEditorPlugin
           (GodotEditorSceneImporter -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_scene_import_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_export_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_export_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_export_plugin #-}

instance Method "add_export_plugin" GodotEditorPlugin
           (GodotEditorExportPlugin -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_export_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_export_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_export_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_export_plugin #-}

instance Method "remove_export_plugin" GodotEditorPlugin
           (GodotEditorExportPlugin -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_export_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_add_inspector_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "add_inspector_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_add_inspector_plugin #-}

instance Method "add_inspector_plugin" GodotEditorPlugin
           (GodotEditorInspectorPlugin -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_add_inspector_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_remove_inspector_plugin
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "remove_inspector_plugin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_remove_inspector_plugin #-}

instance Method "remove_inspector_plugin" GodotEditorPlugin
           (GodotEditorInspectorPlugin -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_remove_inspector_plugin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_set_input_event_forwarding_always_enabled
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "set_input_event_forwarding_always_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_set_input_event_forwarding_always_enabled
             #-}

instance Method "set_input_event_forwarding_always_enabled"
           GodotEditorPlugin
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorPlugin_set_input_event_forwarding_always_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_set_force_draw_over_forwarding_enabled
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "set_force_draw_over_forwarding_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_set_force_draw_over_forwarding_enabled
             #-}

instance Method "set_force_draw_over_forwarding_enabled"
           GodotEditorPlugin
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorPlugin_set_force_draw_over_forwarding_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_editor_interface
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_editor_interface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_editor_interface #-}

instance Method "get_editor_interface" GodotEditorPlugin
           (IO GodotEditorInterface)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_editor_interface
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorPlugin_get_script_create_dialog
  = unsafePerformIO $
      withCString "EditorPlugin" $
        \ clsNamePtr ->
          withCString "get_script_create_dialog" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorPlugin_get_script_create_dialog #-}

instance Method "get_script_create_dialog" GodotEditorPlugin
           (IO GodotScriptCreateDialog)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorPlugin_get_script_create_dialog
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorImportPlugin = GodotEditorImportPlugin GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotEditorImportPlugin where
        type BaseClass GodotEditorImportPlugin = GodotReference
        super = coerce
bindEditorImportPlugin_get_importer_name
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_importer_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_importer_name #-}

instance Method "get_importer_name" GodotEditorImportPlugin
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_importer_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_visible_name
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_visible_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_visible_name #-}

instance Method "get_visible_name" GodotEditorImportPlugin
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_visible_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_preset_count
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_preset_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_preset_count #-}

instance Method "get_preset_count" GodotEditorImportPlugin (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_preset_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_preset_name
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_preset_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_preset_name #-}

instance Method "get_preset_name" GodotEditorImportPlugin
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_preset_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_recognized_extensions
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_recognized_extensions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_recognized_extensions #-}

instance Method "get_recognized_extensions" GodotEditorImportPlugin
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorImportPlugin_get_recognized_extensions
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_import_options
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_import_options" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_import_options #-}

instance Method "get_import_options" GodotEditorImportPlugin
           (Int -> IO GodotArray)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_import_options
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_save_extension
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_save_extension" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_save_extension #-}

instance Method "get_save_extension" GodotEditorImportPlugin
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_save_extension
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_resource_type
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_resource_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_resource_type #-}

instance Method "get_resource_type" GodotEditorImportPlugin
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_resource_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_priority
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_priority" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_priority #-}

instance Method "get_priority" GodotEditorImportPlugin (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_priority
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_import_order
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_import_order" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_import_order #-}

instance Method "get_import_order" GodotEditorImportPlugin (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_import_order
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_get_option_visibility
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "get_option_visibility" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_get_option_visibility #-}

instance Method "get_option_visibility" GodotEditorImportPlugin
           (GodotString -> GodotDictionary -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_get_option_visibility
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorImportPlugin_import
  = unsafePerformIO $
      withCString "EditorImportPlugin" $
        \ clsNamePtr ->
          withCString "import" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorImportPlugin_import #-}

instance Method "import" GodotEditorImportPlugin
           (GodotString ->
              GodotString ->
                GodotDictionary -> GodotArray -> GodotArray -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorImportPlugin_import (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorScript = GodotEditorScript GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotEditorScript where
        type BaseClass GodotEditorScript = GodotReference
        super = coerce
bindEditorScript__run
  = unsafePerformIO $
      withCString "EditorScript" $
        \ clsNamePtr ->
          withCString "_run" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorScript__run #-}

instance Method "_run" GodotEditorScript (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorScript__run (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorScript_add_root_node
  = unsafePerformIO $
      withCString "EditorScript" $
        \ clsNamePtr ->
          withCString "add_root_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorScript_add_root_node #-}

instance Method "add_root_node" GodotEditorScript
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorScript_add_root_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorScript_get_scene
  = unsafePerformIO $
      withCString "EditorScript" $
        \ clsNamePtr ->
          withCString "get_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorScript_get_scene #-}

instance Method "get_scene" GodotEditorScript (IO GodotNode) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorScript_get_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorScript_get_editor_interface
  = unsafePerformIO $
      withCString "EditorScript" $
        \ clsNamePtr ->
          withCString "get_editor_interface" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorScript_get_editor_interface #-}

instance Method "get_editor_interface" GodotEditorScript
           (IO GodotEditorInterface)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorScript_get_editor_interface
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorSelection = GodotEditorSelection GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotEditorSelection where
        type BaseClass GodotEditorSelection = GodotObject
        super = coerce
bindEditorSelection__node_removed
  = unsafePerformIO $
      withCString "EditorSelection" $
        \ clsNamePtr ->
          withCString "_node_removed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSelection__node_removed #-}

instance Method "_node_removed" GodotEditorSelection
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSelection__node_removed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSelection_clear
  = unsafePerformIO $
      withCString "EditorSelection" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSelection_clear #-}

instance Method "clear" GodotEditorSelection (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSelection_clear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSelection_add_node
  = unsafePerformIO $
      withCString "EditorSelection" $
        \ clsNamePtr ->
          withCString "add_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSelection_add_node #-}

instance Method "add_node" GodotEditorSelection
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSelection_add_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSelection_remove_node
  = unsafePerformIO $
      withCString "EditorSelection" $
        \ clsNamePtr ->
          withCString "remove_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSelection_remove_node #-}

instance Method "remove_node" GodotEditorSelection
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSelection_remove_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSelection_get_selected_nodes
  = unsafePerformIO $
      withCString "EditorSelection" $
        \ clsNamePtr ->
          withCString "get_selected_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSelection_get_selected_nodes #-}

instance Method "get_selected_nodes" GodotEditorSelection
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSelection_get_selected_nodes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSelection_get_transformable_selected_nodes
  = unsafePerformIO $
      withCString "EditorSelection" $
        \ clsNamePtr ->
          withCString "get_transformable_selected_nodes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSelection_get_transformable_selected_nodes
             #-}

instance Method "get_transformable_selected_nodes"
           GodotEditorSelection
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorSelection_get_transformable_selected_nodes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSelection__emit_change
  = unsafePerformIO $
      withCString "EditorSelection" $
        \ clsNamePtr ->
          withCString "_emit_change" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSelection__emit_change #-}

instance Method "_emit_change" GodotEditorSelection (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSelection__emit_change
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorFileDialog = GodotEditorFileDialog GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotEditorFileDialog where
        type BaseClass GodotEditorFileDialog = GodotConfirmationDialog
        super = coerce
bindEditorFileDialog__unhandled_input
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__unhandled_input #-}

instance Method "_unhandled_input" GodotEditorFileDialog
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__unhandled_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__item_selected
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_item_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__item_selected #-}

instance Method "_item_selected" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__item_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__multi_selected
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_multi_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__multi_selected #-}

instance Method "_multi_selected" GodotEditorFileDialog
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__multi_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__items_clear_selection
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_items_clear_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__items_clear_selection #-}

instance Method "_items_clear_selection" GodotEditorFileDialog
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__items_clear_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__item_list_item_rmb_selected
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_item_list_item_rmb_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__item_list_item_rmb_selected #-}

instance Method "_item_list_item_rmb_selected"
           GodotEditorFileDialog
           (Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileDialog__item_list_item_rmb_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__item_list_rmb_clicked
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_item_list_rmb_clicked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__item_list_rmb_clicked #-}

instance Method "_item_list_rmb_clicked" GodotEditorFileDialog
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__item_list_rmb_clicked
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__item_menu_id_pressed
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_item_menu_id_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__item_menu_id_pressed #-}

instance Method "_item_menu_id_pressed" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__item_menu_id_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__item_db_selected
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_item_db_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__item_db_selected #-}

instance Method "_item_db_selected" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__item_db_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__dir_entered
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_dir_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__dir_entered #-}

instance Method "_dir_entered" GodotEditorFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__dir_entered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__file_entered
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_file_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__file_entered #-}

instance Method "_file_entered" GodotEditorFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__file_entered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__action_pressed
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_action_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__action_pressed #-}

instance Method "_action_pressed" GodotEditorFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__action_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__cancel_pressed
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_cancel_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__cancel_pressed #-}

instance Method "_cancel_pressed" GodotEditorFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__cancel_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__filter_selected
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_filter_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__filter_selected #-}

instance Method "_filter_selected" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__filter_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__save_confirm_pressed
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_save_confirm_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__save_confirm_pressed #-}

instance Method "_save_confirm_pressed" GodotEditorFileDialog
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__save_confirm_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_clear_filters
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "clear_filters" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_clear_filters #-}

instance Method "clear_filters" GodotEditorFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_clear_filters
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_add_filter
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "add_filter" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_add_filter #-}

instance Method "add_filter" GodotEditorFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_add_filter (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_get_current_dir
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "get_current_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_get_current_dir #-}

instance Method "get_current_dir" GodotEditorFileDialog
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_get_current_dir
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_get_current_file
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "get_current_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_get_current_file #-}

instance Method "get_current_file" GodotEditorFileDialog
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_get_current_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_get_current_path
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "get_current_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_get_current_path #-}

instance Method "get_current_path" GodotEditorFileDialog
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_get_current_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_current_dir
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_current_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_current_dir #-}

instance Method "set_current_dir" GodotEditorFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_set_current_dir
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_current_file
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_current_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_current_file #-}

instance Method "set_current_file" GodotEditorFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_set_current_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_current_path
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_current_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_current_path #-}

instance Method "set_current_path" GodotEditorFileDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_set_current_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_mode
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_mode #-}

instance Method "set_mode" GodotEditorFileDialog (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_set_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_get_mode
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_get_mode #-}

instance Method "get_mode" GodotEditorFileDialog (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_get_mode (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_get_vbox
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "get_vbox" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_get_vbox #-}

instance Method "get_vbox" GodotEditorFileDialog
           (IO GodotVBoxContainer)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_get_vbox (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_access
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_access" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_access #-}

instance Method "set_access" GodotEditorFileDialog (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_set_access (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_get_access
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "get_access" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_get_access #-}

instance Method "get_access" GodotEditorFileDialog (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_get_access (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_show_hidden_files
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_show_hidden_files" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_show_hidden_files #-}

instance Method "set_show_hidden_files" GodotEditorFileDialog
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_set_show_hidden_files
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_is_showing_hidden_files
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "is_showing_hidden_files" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_is_showing_hidden_files #-}

instance Method "is_showing_hidden_files" GodotEditorFileDialog
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_is_showing_hidden_files
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__select_drive
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_select_drive" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__select_drive #-}

instance Method "_select_drive" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__select_drive
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__make_dir
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_make_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__make_dir #-}

instance Method "_make_dir" GodotEditorFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__make_dir (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__make_dir_confirm
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_make_dir_confirm" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__make_dir_confirm #-}

instance Method "_make_dir_confirm" GodotEditorFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__make_dir_confirm
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__update_file_list
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_update_file_list" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__update_file_list #-}

instance Method "_update_file_list" GodotEditorFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__update_file_list
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__update_dir
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_update_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__update_dir #-}

instance Method "_update_dir" GodotEditorFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__update_dir
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__thumbnail_done
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_thumbnail_done" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__thumbnail_done #-}

instance Method "_thumbnail_done" GodotEditorFileDialog
           (GodotString ->
              GodotTexture -> GodotTexture -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__thumbnail_done
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_display_mode
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_display_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_display_mode #-}

instance Method "set_display_mode" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_set_display_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_get_display_mode
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "get_display_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_get_display_mode #-}

instance Method "get_display_mode" GodotEditorFileDialog (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_get_display_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__thumbnail_result
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_thumbnail_result" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__thumbnail_result #-}

instance Method "_thumbnail_result" GodotEditorFileDialog
           (GodotString ->
              GodotTexture -> GodotTexture -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__thumbnail_result
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_set_disable_overwrite_warning
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "set_disable_overwrite_warning" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_set_disable_overwrite_warning #-}

instance Method "set_disable_overwrite_warning"
           GodotEditorFileDialog
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileDialog_set_disable_overwrite_warning
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_is_overwrite_warning_disabled
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "is_overwrite_warning_disabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_is_overwrite_warning_disabled #-}

instance Method "is_overwrite_warning_disabled"
           GodotEditorFileDialog
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileDialog_is_overwrite_warning_disabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__recent_selected
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_recent_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__recent_selected #-}

instance Method "_recent_selected" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__recent_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__go_back
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_go_back" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__go_back #-}

instance Method "_go_back" GodotEditorFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__go_back (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__go_forward
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_go_forward" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__go_forward #-}

instance Method "_go_forward" GodotEditorFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__go_forward
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__go_up
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_go_up" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__go_up #-}

instance Method "_go_up" GodotEditorFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__go_up (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__favorite_toggled
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_favorite_toggled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__favorite_toggled #-}

instance Method "_favorite_toggled" GodotEditorFileDialog
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__favorite_toggled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__favorite_selected
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_favorite_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__favorite_selected #-}

instance Method "_favorite_selected" GodotEditorFileDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__favorite_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__favorite_move_up
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_favorite_move_up" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__favorite_move_up #-}

instance Method "_favorite_move_up" GodotEditorFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__favorite_move_up
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog__favorite_move_down
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "_favorite_move_down" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog__favorite_move_down #-}

instance Method "_favorite_move_down" GodotEditorFileDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog__favorite_move_down
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileDialog_invalidate
  = unsafePerformIO $
      withCString "EditorFileDialog" $
        \ clsNamePtr ->
          withCString "invalidate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileDialog_invalidate #-}

instance Method "invalidate" GodotEditorFileDialog (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileDialog_invalidate (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorSettings = GodotEditorSettings GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotEditorSettings where
        type BaseClass GodotEditorSettings = GodotResource
        super = coerce
bindEditorSettings_has_setting
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "has_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_has_setting #-}

instance Method "has_setting" GodotEditorSettings
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_has_setting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_set_setting
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "set_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_set_setting #-}

instance Method "set_setting" GodotEditorSettings
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_set_setting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_get_setting
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "get_setting" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_get_setting #-}

instance Method "get_setting" GodotEditorSettings
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_get_setting (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_erase
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "erase" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_erase #-}

instance Method "erase" GodotEditorSettings (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_erase (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_set_initial_value
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "set_initial_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_set_initial_value #-}

instance Method "set_initial_value" GodotEditorSettings
           (GodotString -> GodotVariant -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_set_initial_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_property_can_revert
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "property_can_revert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_property_can_revert #-}

instance Method "property_can_revert" GodotEditorSettings
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_property_can_revert
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_property_get_revert
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "property_get_revert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_property_get_revert #-}

instance Method "property_get_revert" GodotEditorSettings
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_property_get_revert
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_add_property_info
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "add_property_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_add_property_info #-}

instance Method "add_property_info" GodotEditorSettings
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_add_property_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_get_settings_dir
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "get_settings_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_get_settings_dir #-}

instance Method "get_settings_dir" GodotEditorSettings
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_get_settings_dir
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_get_project_settings_dir
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "get_project_settings_dir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_get_project_settings_dir #-}

instance Method "get_project_settings_dir" GodotEditorSettings
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_get_project_settings_dir
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_set_project_metadata
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "set_project_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_set_project_metadata #-}

instance Method "set_project_metadata" GodotEditorSettings
           (GodotString -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_set_project_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_get_project_metadata
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "get_project_metadata" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_get_project_metadata #-}

instance Method "get_project_metadata" GodotEditorSettings
           (GodotString -> GodotString -> GodotVariant -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_get_project_metadata
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_set_favorites
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "set_favorites" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_set_favorites #-}

instance Method "set_favorites" GodotEditorSettings
           (GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_set_favorites
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_get_favorites
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "get_favorites" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_get_favorites #-}

instance Method "get_favorites" GodotEditorSettings
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_get_favorites
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_set_recent_dirs
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "set_recent_dirs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_set_recent_dirs #-}

instance Method "set_recent_dirs" GodotEditorSettings
           (GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_set_recent_dirs
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSettings_get_recent_dirs
  = unsafePerformIO $
      withCString "EditorSettings" $
        \ clsNamePtr ->
          withCString "get_recent_dirs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSettings_get_recent_dirs #-}

instance Method "get_recent_dirs" GodotEditorSettings
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSettings_get_recent_dirs
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorSpatialGizmo = GodotEditorSpatialGizmo GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotEditorSpatialGizmo where
        type BaseClass GodotEditorSpatialGizmo = GodotSpatialGizmo
        super = coerce
bindEditorSpatialGizmo_redraw
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "redraw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_redraw #-}

instance Method "redraw" GodotEditorSpatialGizmo (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_redraw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_get_handle_name
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "get_handle_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_get_handle_name #-}

instance Method "get_handle_name" GodotEditorSpatialGizmo
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_get_handle_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_get_handle_value
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "get_handle_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_get_handle_value #-}

instance Method "get_handle_value" GodotEditorSpatialGizmo
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_get_handle_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_set_handle
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "set_handle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_set_handle #-}

instance Method "set_handle" GodotEditorSpatialGizmo
           (Int -> GodotCamera -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_set_handle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_commit_handle
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "commit_handle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_commit_handle #-}

instance Method "commit_handle" GodotEditorSpatialGizmo
           (Int -> GodotVariant -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_commit_handle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_add_lines
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "add_lines" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_add_lines #-}

instance Method "add_lines" GodotEditorSpatialGizmo
           (GodotPoolVector3Array -> GodotMaterial -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_add_lines
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_add_mesh
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "add_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_add_mesh #-}

instance Method "add_mesh" GodotEditorSpatialGizmo
           (GodotArrayMesh -> Bool -> GodotRid -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_add_mesh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_add_collision_segments
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "add_collision_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_add_collision_segments #-}

instance Method "add_collision_segments" GodotEditorSpatialGizmo
           (GodotPoolVector3Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorSpatialGizmo_add_collision_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_add_collision_triangles
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "add_collision_triangles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_add_collision_triangles #-}

instance Method "add_collision_triangles" GodotEditorSpatialGizmo
           (GodotTriangleMesh -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorSpatialGizmo_add_collision_triangles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_add_unscaled_billboard
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "add_unscaled_billboard" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_add_unscaled_billboard #-}

instance Method "add_unscaled_billboard" GodotEditorSpatialGizmo
           (GodotMaterial -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorSpatialGizmo_add_unscaled_billboard
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_add_handles
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "add_handles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_add_handles #-}

instance Method "add_handles" GodotEditorSpatialGizmo
           (GodotPoolVector3Array -> GodotMaterial -> Bool -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_add_handles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_set_spatial_node
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "set_spatial_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_set_spatial_node #-}

instance Method "set_spatial_node" GodotEditorSpatialGizmo
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_set_spatial_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_clear
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_clear #-}

instance Method "clear" GodotEditorSpatialGizmo (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_clear (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSpatialGizmo_set_hidden
  = unsafePerformIO $
      withCString "EditorSpatialGizmo" $
        \ clsNamePtr ->
          withCString "set_hidden" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSpatialGizmo_set_hidden #-}

instance Method "set_hidden" GodotEditorSpatialGizmo
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSpatialGizmo_set_hidden
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorResourcePreview = GodotEditorResourcePreview GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotEditorResourcePreview where
        type BaseClass GodotEditorResourcePreview = GodotNode
        super = coerce
bindEditorResourcePreview__preview_ready
  = unsafePerformIO $
      withCString "EditorResourcePreview" $
        \ clsNamePtr ->
          withCString "_preview_ready" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreview__preview_ready #-}

instance Method "_preview_ready" GodotEditorResourcePreview
           (GodotString ->
              GodotTexture ->
                GodotTexture -> Int -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorResourcePreview__preview_ready
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourcePreview_queue_resource_preview
  = unsafePerformIO $
      withCString "EditorResourcePreview" $
        \ clsNamePtr ->
          withCString "queue_resource_preview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreview_queue_resource_preview #-}

instance Method "queue_resource_preview" GodotEditorResourcePreview
           (GodotString ->
              GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorResourcePreview_queue_resource_preview
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourcePreview_queue_edited_resource_preview
  = unsafePerformIO $
      withCString "EditorResourcePreview" $
        \ clsNamePtr ->
          withCString "queue_edited_resource_preview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreview_queue_edited_resource_preview
             #-}

instance Method "queue_edited_resource_preview"
           GodotEditorResourcePreview
           (GodotResource ->
              GodotObject -> GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorResourcePreview_queue_edited_resource_preview
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourcePreview_add_preview_generator
  = unsafePerformIO $
      withCString "EditorResourcePreview" $
        \ clsNamePtr ->
          withCString "add_preview_generator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreview_add_preview_generator #-}

instance Method "add_preview_generator" GodotEditorResourcePreview
           (GodotEditorResourcePreviewGenerator -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorResourcePreview_add_preview_generator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourcePreview_remove_preview_generator
  = unsafePerformIO $
      withCString "EditorResourcePreview" $
        \ clsNamePtr ->
          withCString "remove_preview_generator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreview_remove_preview_generator #-}

instance Method "remove_preview_generator"
           GodotEditorResourcePreview
           (GodotEditorResourcePreviewGenerator -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorResourcePreview_remove_preview_generator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourcePreview_check_for_invalidation
  = unsafePerformIO $
      withCString "EditorResourcePreview" $
        \ clsNamePtr ->
          withCString "check_for_invalidation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreview_check_for_invalidation #-}

instance Method "check_for_invalidation" GodotEditorResourcePreview
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorResourcePreview_check_for_invalidation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorResourcePreviewGenerator = GodotEditorResourcePreviewGenerator GodotObject
                                                deriving newtype AsVariant

instance HasBaseClass GodotEditorResourcePreviewGenerator where
        type BaseClass GodotEditorResourcePreviewGenerator = GodotReference
        super = coerce
bindEditorResourcePreviewGenerator_handles
  = unsafePerformIO $
      withCString "EditorResourcePreviewGenerator" $
        \ clsNamePtr ->
          withCString "handles" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreviewGenerator_handles #-}

instance Method "handles" GodotEditorResourcePreviewGenerator
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorResourcePreviewGenerator_handles
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourcePreviewGenerator_generate
  = unsafePerformIO $
      withCString "EditorResourcePreviewGenerator" $
        \ clsNamePtr ->
          withCString "generate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreviewGenerator_generate #-}

instance Method "generate" GodotEditorResourcePreviewGenerator
           (GodotResource -> GodotVector2 -> IO GodotTexture)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorResourcePreviewGenerator_generate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourcePreviewGenerator_generate_from_path
  = unsafePerformIO $
      withCString "EditorResourcePreviewGenerator" $
        \ clsNamePtr ->
          withCString "generate_from_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourcePreviewGenerator_generate_from_path
             #-}

instance Method "generate_from_path"
           GodotEditorResourcePreviewGenerator
           (GodotString -> GodotVector2 -> IO GodotTexture)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorResourcePreviewGenerator_generate_from_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorFileSystem = GodotEditorFileSystem GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotEditorFileSystem where
        type BaseClass GodotEditorFileSystem = GodotNode
        super = coerce
bindEditorFileSystem_get_filesystem
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "get_filesystem" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_get_filesystem #-}

instance Method "get_filesystem" GodotEditorFileSystem
           (IO GodotEditorFileSystemDirectory)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_get_filesystem
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_is_scanning
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "is_scanning" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_is_scanning #-}

instance Method "is_scanning" GodotEditorFileSystem (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_is_scanning
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_get_scanning_progress
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "get_scanning_progress" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_get_scanning_progress #-}

instance Method "get_scanning_progress" GodotEditorFileSystem
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_get_scanning_progress
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_scan
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "scan" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_scan #-}

instance Method "scan" GodotEditorFileSystem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_scan (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_scan_sources
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "scan_sources" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_scan_sources #-}

instance Method "scan_sources" GodotEditorFileSystem (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_scan_sources
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_update_file
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "update_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_update_file #-}

instance Method "update_file" GodotEditorFileSystem
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_update_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_get_filesystem_path
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "get_filesystem_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_get_filesystem_path #-}

instance Method "get_filesystem_path" GodotEditorFileSystem
           (GodotString -> IO GodotEditorFileSystemDirectory)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_get_filesystem_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_get_file_type
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "get_file_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_get_file_type #-}

instance Method "get_file_type" GodotEditorFileSystem
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_get_file_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystem_update_script_classes
  = unsafePerformIO $
      withCString "EditorFileSystem" $
        \ clsNamePtr ->
          withCString "update_script_classes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystem_update_script_classes #-}

instance Method "update_script_classes" GodotEditorFileSystem
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystem_update_script_classes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorFileSystemDirectory = GodotEditorFileSystemDirectory GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotEditorFileSystemDirectory where
        type BaseClass GodotEditorFileSystemDirectory = GodotObject
        super = coerce
bindEditorFileSystemDirectory_get_subdir_count
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_subdir_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_subdir_count #-}

instance Method "get_subdir_count" GodotEditorFileSystemDirectory
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileSystemDirectory_get_subdir_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_subdir
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_subdir" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_subdir #-}

instance Method "get_subdir" GodotEditorFileSystemDirectory
           (Int -> IO GodotEditorFileSystemDirectory)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_subdir
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_file_count
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_file_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_file_count #-}

instance Method "get_file_count" GodotEditorFileSystemDirectory
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_file_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_file
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_file #-}

instance Method "get_file" GodotEditorFileSystemDirectory
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_file_path
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_file_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_file_path #-}

instance Method "get_file_path" GodotEditorFileSystemDirectory
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_file_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_file_type
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_file_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_file_type #-}

instance Method "get_file_type" GodotEditorFileSystemDirectory
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_file_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_file_script_class_name
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_file_script_class_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_file_script_class_name
             #-}

instance Method "get_file_script_class_name"
           GodotEditorFileSystemDirectory
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileSystemDirectory_get_file_script_class_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_file_script_class_extends
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_file_script_class_extends" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_file_script_class_extends
             #-}

instance Method "get_file_script_class_extends"
           GodotEditorFileSystemDirectory
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileSystemDirectory_get_file_script_class_extends
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_file_import_is_valid
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_file_import_is_valid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_file_import_is_valid
             #-}

instance Method "get_file_import_is_valid"
           GodotEditorFileSystemDirectory
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileSystemDirectory_get_file_import_is_valid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_name
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_name #-}

instance Method "get_name" GodotEditorFileSystemDirectory
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_path
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_path #-}

instance Method "get_path" GodotEditorFileSystemDirectory
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_get_parent
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "get_parent" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_get_parent #-}

instance Method "get_parent" GodotEditorFileSystemDirectory
           (IO GodotEditorFileSystemDirectory)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_get_parent
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_find_file_index
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "find_file_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_find_file_index #-}

instance Method "find_file_index" GodotEditorFileSystemDirectory
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorFileSystemDirectory_find_file_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorFileSystemDirectory_find_dir_index
  = unsafePerformIO $
      withCString "EditorFileSystemDirectory" $
        \ clsNamePtr ->
          withCString "find_dir_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorFileSystemDirectory_find_dir_index #-}

instance Method "find_dir_index" GodotEditorFileSystemDirectory
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorFileSystemDirectory_find_dir_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotScriptEditor = GodotScriptEditor GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotScriptEditor where
        type BaseClass GodotScriptEditor = GodotPanelContainer
        super = coerce
bindScriptEditor__file_dialog_action
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_file_dialog_action" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__file_dialog_action #-}

instance Method "_file_dialog_action" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__file_dialog_action
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__tab_changed
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_tab_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__tab_changed #-}

instance Method "_tab_changed" GodotScriptEditor (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__tab_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__menu_option
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_menu_option" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__menu_option #-}

instance Method "_menu_option" GodotScriptEditor (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__menu_option (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__close_current_tab
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_close_current_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__close_current_tab #-}

instance Method "_close_current_tab" GodotScriptEditor (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__close_current_tab
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__close_discard_current_tab
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_close_discard_current_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__close_discard_current_tab #-}

instance Method "_close_discard_current_tab" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__close_discard_current_tab
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__close_docs_tab
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_close_docs_tab" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__close_docs_tab #-}

instance Method "_close_docs_tab" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__close_docs_tab
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__close_all_tabs
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_close_all_tabs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__close_all_tabs #-}

instance Method "_close_all_tabs" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__close_all_tabs
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__close_other_tabs
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_close_other_tabs" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__close_other_tabs #-}

instance Method "_close_other_tabs" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__close_other_tabs
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__open_recent_script
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_open_recent_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__open_recent_script #-}

instance Method "_open_recent_script" GodotScriptEditor
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__open_recent_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__theme_option
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_theme_option" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__theme_option #-}

instance Method "_theme_option" GodotScriptEditor (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__theme_option (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__editor_play
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_editor_play" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__editor_play #-}

instance Method "_editor_play" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__editor_play (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__editor_pause
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_editor_pause" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__editor_pause #-}

instance Method "_editor_pause" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__editor_pause (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__editor_stop
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_editor_stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__editor_stop #-}

instance Method "_editor_stop" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__editor_stop (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__add_callback
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_add_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__add_callback #-}

instance Method "_add_callback" GodotScriptEditor
           (GodotObject -> GodotString -> GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__add_callback (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__reload_scripts
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_reload_scripts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__reload_scripts #-}

instance Method "_reload_scripts" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__reload_scripts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__resave_scripts
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_resave_scripts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__resave_scripts #-}

instance Method "_resave_scripts" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__resave_scripts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__res_saved_callback
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_res_saved_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__res_saved_callback #-}

instance Method "_res_saved_callback" GodotScriptEditor
           (GodotResource -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__res_saved_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__goto_script_line
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_goto_script_line" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__goto_script_line #-}

instance Method "_goto_script_line" GodotScriptEditor
           (GodotReference -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__goto_script_line
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__goto_script_line2
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_goto_script_line2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__goto_script_line2 #-}

instance Method "_goto_script_line2" GodotScriptEditor
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__goto_script_line2
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__help_search
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_help_search" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__help_search #-}

instance Method "_help_search" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__help_search (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__help_index
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_help_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__help_index #-}

instance Method "_help_index" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__help_index (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__save_history
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_save_history" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__save_history #-}

instance Method "_save_history" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__save_history (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__copy_script_path
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_copy_script_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__copy_script_path #-}

instance Method "_copy_script_path" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__copy_script_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__breaked
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_breaked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__breaked #-}

instance Method "_breaked" GodotScriptEditor
           (Bool -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__breaked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__show_debugger
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_show_debugger" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__show_debugger #-}

instance Method "_show_debugger" GodotScriptEditor (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__show_debugger (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__get_debug_tooltip
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_get_debug_tooltip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__get_debug_tooltip #-}

instance Method "_get_debug_tooltip" GodotScriptEditor
           (GodotString -> GodotObject -> IO GodotString)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__get_debug_tooltip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__autosave_scripts
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_autosave_scripts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__autosave_scripts #-}

instance Method "_autosave_scripts" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__autosave_scripts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__editor_settings_changed
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_editor_settings_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__editor_settings_changed #-}

instance Method "_editor_settings_changed" GodotScriptEditor
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__editor_settings_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__update_script_names
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_update_script_names" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__update_script_names #-}

instance Method "_update_script_names" GodotScriptEditor (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__update_script_names
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__tree_changed
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_tree_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__tree_changed #-}

instance Method "_tree_changed" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__tree_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__members_overview_selected
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_members_overview_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__members_overview_selected #-}

instance Method "_members_overview_selected" GodotScriptEditor
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__members_overview_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__help_overview_selected
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_help_overview_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__help_overview_selected #-}

instance Method "_help_overview_selected" GodotScriptEditor
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__help_overview_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__script_selected
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_script_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__script_selected #-}

instance Method "_script_selected" GodotScriptEditor (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__script_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__script_created
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_script_created" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__script_created #-}

instance Method "_script_created" GodotScriptEditor
           (GodotScript -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__script_created
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__script_split_dragged
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_script_split_dragged" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__script_split_dragged #-}

instance Method "_script_split_dragged" GodotScriptEditor
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__script_split_dragged
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__help_class_open
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_help_class_open" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__help_class_open #-}

instance Method "_help_class_open" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__help_class_open
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__help_class_goto
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_help_class_goto" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__help_class_goto #-}

instance Method "_help_class_goto" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__help_class_goto
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__request_help
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_request_help" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__request_help #-}

instance Method "_request_help" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__request_help (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__history_forward
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_history_forward" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__history_forward #-}

instance Method "_history_forward" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__history_forward
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__history_back
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_history_back" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__history_back #-}

instance Method "_history_back" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__history_back (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__live_auto_reload_running_scripts
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_live_auto_reload_running_scripts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__live_auto_reload_running_scripts #-}

instance Method "_live_auto_reload_running_scripts"
           GodotScriptEditor
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindScriptEditor__live_auto_reload_running_scripts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__unhandled_input
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_unhandled_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__unhandled_input #-}

instance Method "_unhandled_input" GodotScriptEditor
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__unhandled_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__script_list_gui_input
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_script_list_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__script_list_gui_input #-}

instance Method "_script_list_gui_input" GodotScriptEditor
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__script_list_gui_input
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__toggle_members_overview_alpha_sort
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_toggle_members_overview_alpha_sort" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__toggle_members_overview_alpha_sort
             #-}

instance Method "_toggle_members_overview_alpha_sort"
           GodotScriptEditor
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindScriptEditor__toggle_members_overview_alpha_sort
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__update_members_overview
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_update_members_overview" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__update_members_overview #-}

instance Method "_update_members_overview" GodotScriptEditor
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__update_members_overview
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__script_changed
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_script_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__script_changed #-}

instance Method "_script_changed" GodotScriptEditor (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__script_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__update_recent_scripts
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_update_recent_scripts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__update_recent_scripts #-}

instance Method "_update_recent_scripts" GodotScriptEditor (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__update_recent_scripts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__on_find_in_files_requested
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_on_find_in_files_requested" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__on_find_in_files_requested #-}

instance Method "_on_find_in_files_requested" GodotScriptEditor
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__on_find_in_files_requested
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__start_find_in_files
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_start_find_in_files" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__start_find_in_files #-}

instance Method "_start_find_in_files" GodotScriptEditor
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor__start_find_in_files
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__on_find_in_files_result_selected
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_on_find_in_files_result_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__on_find_in_files_result_selected #-}

instance Method "_on_find_in_files_result_selected"
           GodotScriptEditor
           (GodotString -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindScriptEditor__on_find_in_files_result_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor__on_find_in_files_modified_files
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "_on_find_in_files_modified_files" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor__on_find_in_files_modified_files #-}

instance Method "_on_find_in_files_modified_files"
           GodotScriptEditor
           (GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindScriptEditor__on_find_in_files_modified_files
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor_get_drag_data_fw
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "get_drag_data_fw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor_get_drag_data_fw #-}

instance Method "get_drag_data_fw" GodotScriptEditor
           (GodotVector2 -> GodotObject -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor_get_drag_data_fw
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor_can_drop_data_fw
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "can_drop_data_fw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor_can_drop_data_fw #-}

instance Method "can_drop_data_fw" GodotScriptEditor
           (GodotVector2 -> GodotVariant -> GodotObject -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor_can_drop_data_fw
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor_drop_data_fw
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "drop_data_fw" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor_drop_data_fw #-}

instance Method "drop_data_fw" GodotScriptEditor
           (GodotVector2 -> GodotVariant -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor_drop_data_fw (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor_get_current_script
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "get_current_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor_get_current_script #-}

instance Method "get_current_script" GodotScriptEditor
           (IO GodotScript)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor_get_current_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor_get_open_scripts
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "get_open_scripts" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor_get_open_scripts #-}

instance Method "get_open_scripts" GodotScriptEditor
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor_get_open_scripts
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptEditor_open_script_create_dialog
  = unsafePerformIO $
      withCString "ScriptEditor" $
        \ clsNamePtr ->
          withCString "open_script_create_dialog" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptEditor_open_script_create_dialog #-}

instance Method "open_script_create_dialog" GodotScriptEditor
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptEditor_open_script_create_dialog
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorInterface = GodotEditorInterface GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotEditorInterface where
        type BaseClass GodotEditorInterface = GodotNode
        super = coerce
bindEditorInterface_inspect_object
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "inspect_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_inspect_object #-}

instance Method "inspect_object" GodotEditorInterface
           (GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_inspect_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_selection
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_selection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_selection #-}

instance Method "get_selection" GodotEditorInterface
           (IO GodotEditorSelection)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_selection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_editor_settings
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_editor_settings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_editor_settings #-}

instance Method "get_editor_settings" GodotEditorInterface
           (IO GodotEditorSettings)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_editor_settings
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_script_editor
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_script_editor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_script_editor #-}

instance Method "get_script_editor" GodotEditorInterface
           (IO GodotScriptEditor)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_script_editor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_base_control
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_base_control" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_base_control #-}

instance Method "get_base_control" GodotEditorInterface
           (IO GodotControl)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_base_control
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_edit_resource
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "edit_resource" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_edit_resource #-}

instance Method "edit_resource" GodotEditorInterface
           (GodotResource -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_edit_resource
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_open_scene_from_path
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "open_scene_from_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_open_scene_from_path #-}

instance Method "open_scene_from_path" GodotEditorInterface
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_open_scene_from_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_reload_scene_from_path
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "reload_scene_from_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_reload_scene_from_path #-}

instance Method "reload_scene_from_path" GodotEditorInterface
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_reload_scene_from_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_open_scenes
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_open_scenes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_open_scenes #-}

instance Method "get_open_scenes" GodotEditorInterface
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_open_scenes
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_edited_scene_root
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_edited_scene_root" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_edited_scene_root #-}

instance Method "get_edited_scene_root" GodotEditorInterface
           (IO GodotNode)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_edited_scene_root
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_resource_previewer
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_resource_previewer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_resource_previewer #-}

instance Method "get_resource_previewer" GodotEditorInterface
           (IO GodotEditorResourcePreview)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_resource_previewer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_resource_filesystem
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_resource_filesystem" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_resource_filesystem #-}

instance Method "get_resource_filesystem" GodotEditorInterface
           (IO GodotEditorFileSystem)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_resource_filesystem
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_editor_viewport
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_editor_viewport" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_editor_viewport #-}

instance Method "get_editor_viewport" GodotEditorInterface
           (IO GodotControl)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_editor_viewport
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_make_mesh_previews
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "make_mesh_previews" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_make_mesh_previews #-}

instance Method "make_mesh_previews" GodotEditorInterface
           (GodotArray -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_make_mesh_previews
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_select_file
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "select_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_select_file #-}

instance Method "select_file" GodotEditorInterface
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_select_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_get_selected_path
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "get_selected_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_get_selected_path #-}

instance Method "get_selected_path" GodotEditorInterface
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_get_selected_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_set_plugin_enabled
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "set_plugin_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_set_plugin_enabled #-}

instance Method "set_plugin_enabled" GodotEditorInterface
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_set_plugin_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_is_plugin_enabled
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "is_plugin_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_is_plugin_enabled #-}

instance Method "is_plugin_enabled" GodotEditorInterface
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_is_plugin_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_save_scene
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "save_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_save_scene #-}

instance Method "save_scene" GodotEditorInterface (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_save_scene (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInterface_save_scene_as
  = unsafePerformIO $
      withCString "EditorInterface" $
        \ clsNamePtr ->
          withCString "save_scene_as" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInterface_save_scene_as #-}

instance Method "save_scene_as" GodotEditorInterface
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInterface_save_scene_as
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorExportPlugin = GodotEditorExportPlugin GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotEditorExportPlugin where
        type BaseClass GodotEditorExportPlugin = GodotReference
        super = coerce
bindEditorExportPlugin__export_file
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "_export_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin__export_file #-}

instance Method "_export_file" GodotEditorExportPlugin
           (GodotString -> GodotString -> GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin__export_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin__export_begin
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "_export_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin__export_begin #-}

instance Method "_export_begin" GodotEditorExportPlugin
           (GodotPoolStringArray -> Bool -> GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin__export_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_add_shared_object
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "add_shared_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_add_shared_object #-}

instance Method "add_shared_object" GodotEditorExportPlugin
           (GodotString -> GodotPoolStringArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_add_shared_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_add_file
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "add_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_add_file #-}

instance Method "add_file" GodotEditorExportPlugin
           (GodotString -> GodotPoolByteArray -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_add_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_add_ios_framework
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "add_ios_framework" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_add_ios_framework #-}

instance Method "add_ios_framework" GodotEditorExportPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_add_ios_framework
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_add_ios_plist_content
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "add_ios_plist_content" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_add_ios_plist_content #-}

instance Method "add_ios_plist_content" GodotEditorExportPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_add_ios_plist_content
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_add_ios_linker_flags
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "add_ios_linker_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_add_ios_linker_flags #-}

instance Method "add_ios_linker_flags" GodotEditorExportPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_add_ios_linker_flags
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_add_ios_bundle_file
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "add_ios_bundle_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_add_ios_bundle_file #-}

instance Method "add_ios_bundle_file" GodotEditorExportPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_add_ios_bundle_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_add_ios_cpp_code
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "add_ios_cpp_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_add_ios_cpp_code #-}

instance Method "add_ios_cpp_code" GodotEditorExportPlugin
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_add_ios_cpp_code
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorExportPlugin_skip
  = unsafePerformIO $
      withCString "EditorExportPlugin" $
        \ clsNamePtr ->
          withCString "skip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorExportPlugin_skip #-}

instance Method "skip" GodotEditorExportPlugin (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorExportPlugin_skip (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorResourceConversionPlugin = GodotEditorResourceConversionPlugin GodotObject
                                                deriving newtype AsVariant

instance HasBaseClass GodotEditorResourceConversionPlugin where
        type BaseClass GodotEditorResourceConversionPlugin = GodotReference
        super = coerce
bindEditorResourceConversionPlugin__convert
  = unsafePerformIO $
      withCString "EditorResourceConversionPlugin" $
        \ clsNamePtr ->
          withCString "_convert" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourceConversionPlugin__convert #-}

instance Method "_convert" GodotEditorResourceConversionPlugin
           (GodotResource -> IO GodotResource)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorResourceConversionPlugin__convert
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorResourceConversionPlugin__converts_to
  = unsafePerformIO $
      withCString "EditorResourceConversionPlugin" $
        \ clsNamePtr ->
          withCString "_converts_to" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorResourceConversionPlugin__converts_to #-}

instance Method "_converts_to" GodotEditorResourceConversionPlugin
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorResourceConversionPlugin__converts_to
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorSceneImporter = GodotEditorSceneImporter GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotEditorSceneImporter where
        type BaseClass GodotEditorSceneImporter = GodotReference
        super = coerce
bindEditorSceneImporter__get_import_flags
  = unsafePerformIO $
      withCString "EditorSceneImporter" $
        \ clsNamePtr ->
          withCString "_get_import_flags" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSceneImporter__get_import_flags #-}

instance Method "_get_import_flags" GodotEditorSceneImporter
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSceneImporter__get_import_flags
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSceneImporter__get_extensions
  = unsafePerformIO $
      withCString "EditorSceneImporter" $
        \ clsNamePtr ->
          withCString "_get_extensions" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSceneImporter__get_extensions #-}

instance Method "_get_extensions" GodotEditorSceneImporter
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSceneImporter__get_extensions
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSceneImporter__import_scene
  = unsafePerformIO $
      withCString "EditorSceneImporter" $
        \ clsNamePtr ->
          withCString "_import_scene" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSceneImporter__import_scene #-}

instance Method "_import_scene" GodotEditorSceneImporter
           (GodotString -> Int -> Int -> IO GodotNode)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSceneImporter__import_scene
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSceneImporter__import_animation
  = unsafePerformIO $
      withCString "EditorSceneImporter" $
        \ clsNamePtr ->
          withCString "_import_animation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSceneImporter__import_animation #-}

instance Method "_import_animation" GodotEditorSceneImporter
           (GodotString -> Int -> Int -> IO GodotAnimation)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorSceneImporter__import_animation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSceneImporter_import_scene_from_other_importer
  = unsafePerformIO $
      withCString "EditorSceneImporter" $
        \ clsNamePtr ->
          withCString "import_scene_from_other_importer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSceneImporter_import_scene_from_other_importer
             #-}

instance Method "import_scene_from_other_importer"
           GodotEditorSceneImporter
           (GodotString -> Int -> Int -> IO GodotNode)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorSceneImporter_import_scene_from_other_importer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorSceneImporter_import_animation_from_other_importer
  = unsafePerformIO $
      withCString "EditorSceneImporter" $
        \ clsNamePtr ->
          withCString "import_animation_from_other_importer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorSceneImporter_import_animation_from_other_importer
             #-}

instance Method "import_animation_from_other_importer"
           GodotEditorSceneImporter
           (GodotString -> Int -> Int -> IO GodotAnimation)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorSceneImporter_import_animation_from_other_importer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorInspector = GodotEditorInspector GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotEditorInspector where
        type BaseClass GodotEditorInspector = GodotScrollContainer
        super = coerce
bindEditorInspector__property_changed
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_property_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__property_changed #-}

instance Method "_property_changed" GodotEditorInspector
           (GodotString -> GodotVariant -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__property_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__multiple_properties_changed
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_multiple_properties_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__multiple_properties_changed #-}

instance Method "_multiple_properties_changed" GodotEditorInspector
           (GodotPoolStringArray -> GodotArray -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorInspector__multiple_properties_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__property_changed_update_all
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_property_changed_update_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__property_changed_update_all #-}

instance Method "_property_changed_update_all" GodotEditorInspector
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorInspector__property_changed_update_all
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__edit_request_change
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_edit_request_change" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__edit_request_change #-}

instance Method "_edit_request_change" GodotEditorInspector
           (GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__edit_request_change
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__node_removed
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_node_removed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__node_removed #-}

instance Method "_node_removed" GodotEditorInspector
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__node_removed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__filter_changed
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_filter_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__filter_changed #-}

instance Method "_filter_changed" GodotEditorInspector
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__filter_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__property_keyed
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_property_keyed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__property_keyed #-}

instance Method "_property_keyed" GodotEditorInspector
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__property_keyed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__property_keyed_with_value
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_property_keyed_with_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__property_keyed_with_value #-}

instance Method "_property_keyed_with_value" GodotEditorInspector
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorInspector__property_keyed_with_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__property_checked
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_property_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__property_checked #-}

instance Method "_property_checked" GodotEditorInspector
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__property_checked
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__property_selected
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_property_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__property_selected #-}

instance Method "_property_selected" GodotEditorInspector
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__property_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__resource_selected
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_resource_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__resource_selected #-}

instance Method "_resource_selected" GodotEditorInspector
           (GodotString -> GodotResource -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__resource_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__object_id_selected
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_object_id_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__object_id_selected #-}

instance Method "_object_id_selected" GodotEditorInspector
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__object_id_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector__vscroll_changed
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "_vscroll_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector__vscroll_changed #-}

instance Method "_vscroll_changed" GodotEditorInspector
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector__vscroll_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspector_refresh
  = unsafePerformIO $
      withCString "EditorInspector" $
        \ clsNamePtr ->
          withCString "refresh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspector_refresh #-}

instance Method "refresh" GodotEditorInspector (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspector_refresh (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorInspectorPlugin = GodotEditorInspectorPlugin GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotEditorInspectorPlugin where
        type BaseClass GodotEditorInspectorPlugin = GodotReference
        super = coerce
bindEditorInspectorPlugin_can_handle
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "can_handle" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_can_handle #-}

instance Method "can_handle" GodotEditorInspectorPlugin
           (GodotObject -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspectorPlugin_can_handle
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspectorPlugin_parse_begin
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "parse_begin" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_parse_begin #-}

instance Method "parse_begin" GodotEditorInspectorPlugin
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspectorPlugin_parse_begin
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspectorPlugin_parse_category
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "parse_category" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_parse_category #-}

instance Method "parse_category" GodotEditorInspectorPlugin
           (GodotObject -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspectorPlugin_parse_category
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspectorPlugin_parse_property
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "parse_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_parse_property #-}

instance Method "parse_property" GodotEditorInspectorPlugin
           (GodotObject ->
              Int -> GodotString -> Int -> GodotString -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5 arg6
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5, toVariant arg6]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspectorPlugin_parse_property
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspectorPlugin_parse_end
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "parse_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_parse_end #-}

instance Method "parse_end" GodotEditorInspectorPlugin (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspectorPlugin_parse_end
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspectorPlugin_add_custom_control
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "add_custom_control" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_add_custom_control #-}

instance Method "add_custom_control" GodotEditorInspectorPlugin
           (GodotObject -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorInspectorPlugin_add_custom_control
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspectorPlugin_add_property_editor
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "add_property_editor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_add_property_editor #-}

instance Method "add_property_editor" GodotEditorInspectorPlugin
           (GodotString -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorInspectorPlugin_add_property_editor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorInspectorPlugin_add_property_editor_for_multiple_properties
  = unsafePerformIO $
      withCString "EditorInspectorPlugin" $
        \ clsNamePtr ->
          withCString "add_property_editor_for_multiple_properties" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorInspectorPlugin_add_property_editor_for_multiple_properties
             #-}

instance Method "add_property_editor_for_multiple_properties"
           GodotEditorInspectorPlugin
           (GodotString -> GodotPoolStringArray -> GodotObject -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindEditorInspectorPlugin_add_property_editor_for_multiple_properties
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorProperty = GodotEditorProperty GodotObject
                                deriving newtype AsVariant

instance HasBaseClass GodotEditorProperty where
        type BaseClass GodotEditorProperty = GodotContainer
        super = coerce
bindEditorProperty_update_property
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "update_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_update_property #-}

instance Method "update_property" GodotEditorProperty (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_update_property
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_set_label
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "set_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_set_label #-}

instance Method "set_label" GodotEditorProperty
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_set_label (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_get_label
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "get_label" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_get_label #-}

instance Method "get_label" GodotEditorProperty (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_get_label (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_set_read_only
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "set_read_only" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_set_read_only #-}

instance Method "set_read_only" GodotEditorProperty (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_set_read_only
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_is_read_only
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "is_read_only" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_is_read_only #-}

instance Method "is_read_only" GodotEditorProperty (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_is_read_only (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_set_checkable
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "set_checkable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_set_checkable #-}

instance Method "set_checkable" GodotEditorProperty (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_set_checkable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_is_checkable
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "is_checkable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_is_checkable #-}

instance Method "is_checkable" GodotEditorProperty (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_is_checkable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_set_checked
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "set_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_set_checked #-}

instance Method "set_checked" GodotEditorProperty (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_set_checked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_is_checked
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "is_checked" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_is_checked #-}

instance Method "is_checked" GodotEditorProperty (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_is_checked (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_set_draw_red
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "set_draw_red" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_set_draw_red #-}

instance Method "set_draw_red" GodotEditorProperty (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_set_draw_red (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_is_draw_red
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "is_draw_red" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_is_draw_red #-}

instance Method "is_draw_red" GodotEditorProperty (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_is_draw_red (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_set_keying
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "set_keying" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_set_keying #-}

instance Method "set_keying" GodotEditorProperty (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_set_keying (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_is_keying
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "is_keying" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_is_keying #-}

instance Method "is_keying" GodotEditorProperty (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_is_keying (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_get_edited_property
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "get_edited_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_get_edited_property #-}

instance Method "get_edited_property" GodotEditorProperty
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_get_edited_property
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_get_edited_object
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "get_edited_object" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_get_edited_object #-}

instance Method "get_edited_object" GodotEditorProperty
           (IO GodotObject)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_get_edited_object
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty__gui_input
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "_gui_input" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty__gui_input #-}

instance Method "_gui_input" GodotEditorProperty
           (GodotInputEvent -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty__gui_input (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty__focusable_focused
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "_focusable_focused" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty__focusable_focused #-}

instance Method "_focusable_focused" GodotEditorProperty
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty__focusable_focused
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorProperty_get_tooltip_text
  = unsafePerformIO $
      withCString "EditorProperty" $
        \ clsNamePtr ->
          withCString "get_tooltip_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorProperty_get_tooltip_text #-}

instance Method "get_tooltip_text" GodotEditorProperty
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorProperty_get_tooltip_text
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotAnimationTrackEditPlugin = GodotAnimationTrackEditPlugin GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotAnimationTrackEditPlugin where
        type BaseClass GodotAnimationTrackEditPlugin = GodotReference
        super = coerce

newtype GodotScriptCreateDialog = GodotScriptCreateDialog GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotScriptCreateDialog where
        type BaseClass GodotScriptCreateDialog = GodotConfirmationDialog
        super = coerce
bindScriptCreateDialog__class_name_changed
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_class_name_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__class_name_changed #-}

instance Method "_class_name_changed" GodotScriptCreateDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__class_name_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__parent_name_changed
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_parent_name_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__parent_name_changed #-}

instance Method "_parent_name_changed" GodotScriptCreateDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__parent_name_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__lang_changed
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_lang_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__lang_changed #-}

instance Method "_lang_changed" GodotScriptCreateDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__lang_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__built_in_pressed
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_built_in_pressed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__built_in_pressed #-}

instance Method "_built_in_pressed" GodotScriptCreateDialog (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__built_in_pressed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__browse_path
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_browse_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__browse_path #-}

instance Method "_browse_path" GodotScriptCreateDialog
           (Bool -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__browse_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__file_selected
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_file_selected" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__file_selected #-}

instance Method "_file_selected" GodotScriptCreateDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__file_selected
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__path_changed
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_path_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__path_changed #-}

instance Method "_path_changed" GodotScriptCreateDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__path_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__path_entered
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_path_entered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__path_entered #-}

instance Method "_path_entered" GodotScriptCreateDialog
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__path_entered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog__template_changed
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "_template_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog__template_changed #-}

instance Method "_template_changed" GodotScriptCreateDialog
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog__template_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindScriptCreateDialog_config
  = unsafePerformIO $
      withCString "ScriptCreateDialog" $
        \ clsNamePtr ->
          withCString "config" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindScriptCreateDialog_config #-}

instance Method "config" GodotScriptCreateDialog
           (GodotString -> GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindScriptCreateDialog_config (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotEditorScenePostImport = GodotEditorScenePostImport GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotEditorScenePostImport where
        type BaseClass GodotEditorScenePostImport = GodotReference
        super = coerce
bindEditorScenePostImport_post_import
  = unsafePerformIO $
      withCString "EditorScenePostImport" $
        \ clsNamePtr ->
          withCString "post_import" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorScenePostImport_post_import #-}

instance Method "post_import" GodotEditorScenePostImport
           (GodotObject -> IO GodotObject)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorScenePostImport_post_import
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorScenePostImport_get_source_folder
  = unsafePerformIO $
      withCString "EditorScenePostImport" $
        \ clsNamePtr ->
          withCString "get_source_folder" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorScenePostImport_get_source_folder #-}

instance Method "get_source_folder" GodotEditorScenePostImport
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorScenePostImport_get_source_folder
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindEditorScenePostImport_get_source_file
  = unsafePerformIO $
      withCString "EditorScenePostImport" $
        \ clsNamePtr ->
          withCString "get_source_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindEditorScenePostImport_get_source_file #-}

instance Method "get_source_file" GodotEditorScenePostImport
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindEditorScenePostImport_get_source_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotJavaScript = GodotJavaScript GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotJavaScript where
        type BaseClass GodotJavaScript = GodotObject
        super = coerce
bindJavaScript_eval
  = unsafePerformIO $
      withCString "JavaScript" $
        \ clsNamePtr ->
          withCString "eval" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindJavaScript_eval #-}

instance Method "eval" GodotJavaScript
           (GodotString -> Bool -> IO GodotVariant)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindJavaScript_eval (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGShape = GodotCSGShape GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotCSGShape where
        type BaseClass GodotCSGShape = GodotVisualInstance
        super = coerce
bindCSGShape__update_shape
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "_update_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape__update_shape #-}

instance Method "_update_shape" GodotCSGShape (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape__update_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGShape_is_root_shape
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "is_root_shape" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape_is_root_shape #-}

instance Method "is_root_shape" GodotCSGShape (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape_is_root_shape (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGShape_set_operation
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "set_operation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape_set_operation #-}

instance Method "set_operation" GodotCSGShape (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape_set_operation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGShape_get_operation
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "get_operation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape_get_operation #-}

instance Method "get_operation" GodotCSGShape (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape_get_operation (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGShape_set_use_collision
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "set_use_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape_set_use_collision #-}

instance Method "set_use_collision" GodotCSGShape (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape_set_use_collision (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGShape_is_using_collision
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "is_using_collision" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape_is_using_collision #-}

instance Method "is_using_collision" GodotCSGShape (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape_is_using_collision (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGShape_set_snap
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "set_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape_set_snap #-}

instance Method "set_snap" GodotCSGShape (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape_set_snap (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGShape_get_snap
  = unsafePerformIO $
      withCString "CSGShape" $
        \ clsNamePtr ->
          withCString "get_snap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGShape_get_snap #-}

instance Method "get_snap" GodotCSGShape (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGShape_get_snap (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGPrimitive = GodotCSGPrimitive GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotCSGPrimitive where
        type BaseClass GodotCSGPrimitive = GodotCSGShape
        super = coerce
bindCSGPrimitive_set_invert_faces
  = unsafePerformIO $
      withCString "CSGPrimitive" $
        \ clsNamePtr ->
          withCString "set_invert_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPrimitive_set_invert_faces #-}

instance Method "set_invert_faces" GodotCSGPrimitive
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPrimitive_set_invert_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPrimitive_is_inverting_faces
  = unsafePerformIO $
      withCString "CSGPrimitive" $
        \ clsNamePtr ->
          withCString "is_inverting_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPrimitive_is_inverting_faces #-}

instance Method "is_inverting_faces" GodotCSGPrimitive (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPrimitive_is_inverting_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGMesh = GodotCSGMesh GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotCSGMesh where
        type BaseClass GodotCSGMesh = GodotCSGPrimitive
        super = coerce
bindCSGMesh_set_mesh
  = unsafePerformIO $
      withCString "CSGMesh" $
        \ clsNamePtr ->
          withCString "set_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGMesh_set_mesh #-}

instance Method "set_mesh" GodotCSGMesh (GodotMesh -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGMesh_set_mesh (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGMesh_get_mesh
  = unsafePerformIO $
      withCString "CSGMesh" $
        \ clsNamePtr ->
          withCString "get_mesh" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGMesh_get_mesh #-}

instance Method "get_mesh" GodotCSGMesh (IO GodotMesh) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGMesh_get_mesh (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGMesh__mesh_changed
  = unsafePerformIO $
      withCString "CSGMesh" $
        \ clsNamePtr ->
          withCString "_mesh_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGMesh__mesh_changed #-}

instance Method "_mesh_changed" GodotCSGMesh (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGMesh__mesh_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGSphere = GodotCSGSphere GodotObject
                           deriving newtype AsVariant

instance HasBaseClass GodotCSGSphere where
        type BaseClass GodotCSGSphere = GodotCSGPrimitive
        super = coerce
bindCSGSphere_set_radius
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_set_radius #-}

instance Method "set_radius" GodotCSGSphere (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_set_radius (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_get_radius
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_get_radius #-}

instance Method "get_radius" GodotCSGSphere (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_get_radius (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_set_radial_segments
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "set_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_set_radial_segments #-}

instance Method "set_radial_segments" GodotCSGSphere (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_set_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_get_radial_segments
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "get_radial_segments" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_get_radial_segments #-}

instance Method "get_radial_segments" GodotCSGSphere (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_get_radial_segments
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_set_rings
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "set_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_set_rings #-}

instance Method "set_rings" GodotCSGSphere (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_set_rings (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_get_rings
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "get_rings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_get_rings #-}

instance Method "get_rings" GodotCSGSphere (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_get_rings (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_set_smooth_faces
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "set_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_set_smooth_faces #-}

instance Method "set_smooth_faces" GodotCSGSphere (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_set_smooth_faces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_get_smooth_faces
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "get_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_get_smooth_faces #-}

instance Method "get_smooth_faces" GodotCSGSphere (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_get_smooth_faces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_set_material
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_set_material #-}

instance Method "set_material" GodotCSGSphere
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGSphere_get_material
  = unsafePerformIO $
      withCString "CSGSphere" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGSphere_get_material #-}

instance Method "get_material" GodotCSGSphere (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGSphere_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGBox = GodotCSGBox GodotObject
                        deriving newtype AsVariant

instance HasBaseClass GodotCSGBox where
        type BaseClass GodotCSGBox = GodotCSGPrimitive
        super = coerce
bindCSGBox_set_width
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "set_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_set_width #-}

instance Method "set_width" GodotCSGBox (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_set_width (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGBox_get_width
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_get_width #-}

instance Method "get_width" GodotCSGBox (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_get_width (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGBox_set_height
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_set_height #-}

instance Method "set_height" GodotCSGBox (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_set_height (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGBox_get_height
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_get_height #-}

instance Method "get_height" GodotCSGBox (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_get_height (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGBox_set_depth
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "set_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_set_depth #-}

instance Method "set_depth" GodotCSGBox (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_set_depth (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGBox_get_depth
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "get_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_get_depth #-}

instance Method "get_depth" GodotCSGBox (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_get_depth (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGBox_set_material
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_set_material #-}

instance Method "set_material" GodotCSGBox (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_set_material (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGBox_get_material
  = unsafePerformIO $
      withCString "CSGBox" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGBox_get_material #-}

instance Method "get_material" GodotCSGBox (IO GodotMaterial) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGBox_get_material (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGCylinder = GodotCSGCylinder GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotCSGCylinder where
        type BaseClass GodotCSGCylinder = GodotCSGPrimitive
        super = coerce
bindCSGCylinder_set_radius
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "set_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_set_radius #-}

instance Method "set_radius" GodotCSGCylinder (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_set_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_get_radius
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "get_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_get_radius #-}

instance Method "get_radius" GodotCSGCylinder (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_get_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_set_height
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_set_height #-}

instance Method "set_height" GodotCSGCylinder (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_get_height
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_get_height #-}

instance Method "get_height" GodotCSGCylinder (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_set_sides
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "set_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_set_sides #-}

instance Method "set_sides" GodotCSGCylinder (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_set_sides (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_get_sides
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "get_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_get_sides #-}

instance Method "get_sides" GodotCSGCylinder (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_get_sides (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_set_cone
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "set_cone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_set_cone #-}

instance Method "set_cone" GodotCSGCylinder (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_set_cone (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_is_cone
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "is_cone" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_is_cone #-}

instance Method "is_cone" GodotCSGCylinder (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_is_cone (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_set_material
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_set_material #-}

instance Method "set_material" GodotCSGCylinder
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_get_material
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_get_material #-}

instance Method "get_material" GodotCSGCylinder (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_set_smooth_faces
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "set_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_set_smooth_faces #-}

instance Method "set_smooth_faces" GodotCSGCylinder (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_set_smooth_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGCylinder_get_smooth_faces
  = unsafePerformIO $
      withCString "CSGCylinder" $
        \ clsNamePtr ->
          withCString "get_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGCylinder_get_smooth_faces #-}

instance Method "get_smooth_faces" GodotCSGCylinder (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGCylinder_get_smooth_faces
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGTorus = GodotCSGTorus GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotCSGTorus where
        type BaseClass GodotCSGTorus = GodotCSGPrimitive
        super = coerce
bindCSGTorus_set_inner_radius
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "set_inner_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_set_inner_radius #-}

instance Method "set_inner_radius" GodotCSGTorus (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_set_inner_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_get_inner_radius
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "get_inner_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_get_inner_radius #-}

instance Method "get_inner_radius" GodotCSGTorus (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_get_inner_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_set_outer_radius
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "set_outer_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_set_outer_radius #-}

instance Method "set_outer_radius" GodotCSGTorus (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_set_outer_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_get_outer_radius
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "get_outer_radius" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_get_outer_radius #-}

instance Method "get_outer_radius" GodotCSGTorus (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_get_outer_radius (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_set_sides
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "set_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_set_sides #-}

instance Method "set_sides" GodotCSGTorus (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_set_sides (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_get_sides
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "get_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_get_sides #-}

instance Method "get_sides" GodotCSGTorus (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_get_sides (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_set_ring_sides
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "set_ring_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_set_ring_sides #-}

instance Method "set_ring_sides" GodotCSGTorus (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_set_ring_sides (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_get_ring_sides
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "get_ring_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_get_ring_sides #-}

instance Method "get_ring_sides" GodotCSGTorus (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_get_ring_sides (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_set_material
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_set_material #-}

instance Method "set_material" GodotCSGTorus
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_get_material
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_get_material #-}

instance Method "get_material" GodotCSGTorus (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_set_smooth_faces
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "set_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_set_smooth_faces #-}

instance Method "set_smooth_faces" GodotCSGTorus (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_set_smooth_faces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGTorus_get_smooth_faces
  = unsafePerformIO $
      withCString "CSGTorus" $
        \ clsNamePtr ->
          withCString "get_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGTorus_get_smooth_faces #-}

instance Method "get_smooth_faces" GodotCSGTorus (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGTorus_get_smooth_faces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGPolygon = GodotCSGPolygon GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotCSGPolygon where
        type BaseClass GodotCSGPolygon = GodotCSGPrimitive
        super = coerce
bindCSGPolygon_set_polygon
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_polygon #-}

instance Method "set_polygon" GodotCSGPolygon
           (GodotPoolVector2Array -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_polygon
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_polygon #-}

instance Method "get_polygon" GodotCSGPolygon
           (IO GodotPoolVector2Array)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_polygon (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_mode
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_mode #-}

instance Method "set_mode" GodotCSGPolygon (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_mode
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_mode #-}

instance Method "get_mode" GodotCSGPolygon (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_mode (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_depth
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_depth #-}

instance Method "set_depth" GodotCSGPolygon (Float -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_depth (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_depth
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_depth #-}

instance Method "get_depth" GodotCSGPolygon (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_depth (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_spin_degrees
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_spin_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_spin_degrees #-}

instance Method "set_spin_degrees" GodotCSGPolygon (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_spin_degrees (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_spin_degrees
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_spin_degrees" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_spin_degrees #-}

instance Method "get_spin_degrees" GodotCSGPolygon (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_spin_degrees (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_spin_sides
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_spin_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_spin_sides #-}

instance Method "set_spin_sides" GodotCSGPolygon (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_spin_sides (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_spin_sides
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_spin_sides" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_spin_sides #-}

instance Method "get_spin_sides" GodotCSGPolygon (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_spin_sides (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_path_node
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_path_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_path_node #-}

instance Method "set_path_node" GodotCSGPolygon
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_path_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_path_node
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_path_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_path_node #-}

instance Method "get_path_node" GodotCSGPolygon (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_path_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_path_interval
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_path_interval" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_path_interval #-}

instance Method "set_path_interval" GodotCSGPolygon
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_path_interval
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_path_interval
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_path_interval" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_path_interval #-}

instance Method "get_path_interval" GodotCSGPolygon (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_path_interval
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_path_rotation
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_path_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_path_rotation #-}

instance Method "set_path_rotation" GodotCSGPolygon (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_path_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_path_rotation
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_path_rotation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_path_rotation #-}

instance Method "get_path_rotation" GodotCSGPolygon (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_path_rotation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_path_local
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_path_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_path_local #-}

instance Method "set_path_local" GodotCSGPolygon (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_path_local (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_is_path_local
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "is_path_local" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_is_path_local #-}

instance Method "is_path_local" GodotCSGPolygon (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_is_path_local (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_path_continuous_u
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_path_continuous_u" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_path_continuous_u #-}

instance Method "set_path_continuous_u" GodotCSGPolygon
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_path_continuous_u
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_is_path_continuous_u
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "is_path_continuous_u" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_is_path_continuous_u #-}

instance Method "is_path_continuous_u" GodotCSGPolygon (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_is_path_continuous_u
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_path_joined
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_path_joined" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_path_joined #-}

instance Method "set_path_joined" GodotCSGPolygon (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_path_joined (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_is_path_joined
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "is_path_joined" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_is_path_joined #-}

instance Method "is_path_joined" GodotCSGPolygon (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_is_path_joined (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_material
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_material #-}

instance Method "set_material" GodotCSGPolygon
           (GodotMaterial -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_material
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_material" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_material #-}

instance Method "get_material" GodotCSGPolygon (IO GodotMaterial)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_material (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_set_smooth_faces
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "set_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_set_smooth_faces #-}

instance Method "set_smooth_faces" GodotCSGPolygon (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_set_smooth_faces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon_get_smooth_faces
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "get_smooth_faces" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon_get_smooth_faces #-}

instance Method "get_smooth_faces" GodotCSGPolygon (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon_get_smooth_faces (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon__is_editable_3d_polygon
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "_is_editable_3d_polygon" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon__is_editable_3d_polygon #-}

instance Method "_is_editable_3d_polygon" GodotCSGPolygon (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon__is_editable_3d_polygon
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon__has_editable_3d_polygon_no_depth
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "_has_editable_3d_polygon_no_depth" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon__has_editable_3d_polygon_no_depth #-}

instance Method "_has_editable_3d_polygon_no_depth" GodotCSGPolygon
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindCSGPolygon__has_editable_3d_polygon_no_depth
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon__path_exited
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "_path_exited" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon__path_exited #-}

instance Method "_path_exited" GodotCSGPolygon (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon__path_exited (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindCSGPolygon__path_changed
  = unsafePerformIO $
      withCString "CSGPolygon" $
        \ clsNamePtr ->
          withCString "_path_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindCSGPolygon__path_changed #-}

instance Method "_path_changed" GodotCSGPolygon (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindCSGPolygon__path_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotCSGCombiner = GodotCSGCombiner GodotObject
                             deriving newtype AsVariant

instance HasBaseClass GodotCSGCombiner where
        type BaseClass GodotCSGCombiner = GodotCSGShape
        super = coerce

newtype GodotNetworkedMultiplayerENet = GodotNetworkedMultiplayerENet GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotNetworkedMultiplayerENet where
        type BaseClass GodotNetworkedMultiplayerENet =
             GodotNetworkedMultiplayerPeer
        super = coerce
bindNetworkedMultiplayerENet_create_server
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "create_server" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_create_server #-}

instance Method "create_server" GodotNetworkedMultiplayerENet
           (Int -> Int -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerENet_create_server
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_create_client
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "create_client" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_create_client #-}

instance Method "create_client" GodotNetworkedMultiplayerENet
           (GodotString -> Int -> Int -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerENet_create_client
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_close_connection
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "close_connection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_close_connection #-}

instance Method "close_connection" GodotNetworkedMultiplayerENet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_close_connection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_disconnect_peer
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "disconnect_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_disconnect_peer #-}

instance Method "disconnect_peer" GodotNetworkedMultiplayerENet
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerENet_disconnect_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_set_compression_mode
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "set_compression_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_set_compression_mode #-}

instance Method "set_compression_mode"
           GodotNetworkedMultiplayerENet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_set_compression_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_get_compression_mode
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "get_compression_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_get_compression_mode #-}

instance Method "get_compression_mode"
           GodotNetworkedMultiplayerENet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_get_compression_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_set_bind_ip
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "set_bind_ip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_set_bind_ip #-}

instance Method "set_bind_ip" GodotNetworkedMultiplayerENet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerENet_set_bind_ip
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_get_peer_address
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "get_peer_address" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_get_peer_address #-}

instance Method "get_peer_address" GodotNetworkedMultiplayerENet
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_get_peer_address
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_get_peer_port
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "get_peer_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_get_peer_port #-}

instance Method "get_peer_port" GodotNetworkedMultiplayerENet
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNetworkedMultiplayerENet_get_peer_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_get_packet_channel
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "get_packet_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_get_packet_channel #-}

instance Method "get_packet_channel" GodotNetworkedMultiplayerENet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_get_packet_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_get_last_packet_channel
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "get_last_packet_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_get_last_packet_channel
             #-}

instance Method "get_last_packet_channel"
           GodotNetworkedMultiplayerENet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_get_last_packet_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_set_transfer_channel
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "set_transfer_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_set_transfer_channel #-}

instance Method "set_transfer_channel"
           GodotNetworkedMultiplayerENet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_set_transfer_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_get_transfer_channel
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "get_transfer_channel" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_get_transfer_channel #-}

instance Method "get_transfer_channel"
           GodotNetworkedMultiplayerENet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_get_transfer_channel
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_set_channel_count
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "set_channel_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_set_channel_count #-}

instance Method "set_channel_count" GodotNetworkedMultiplayerENet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_set_channel_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_get_channel_count
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "get_channel_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_get_channel_count #-}

instance Method "get_channel_count" GodotNetworkedMultiplayerENet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_get_channel_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_set_always_ordered
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "set_always_ordered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_set_always_ordered #-}

instance Method "set_always_ordered" GodotNetworkedMultiplayerENet
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_set_always_ordered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNetworkedMultiplayerENet_is_always_ordered
  = unsafePerformIO $
      withCString "NetworkedMultiplayerENet" $
        \ clsNamePtr ->
          withCString "is_always_ordered" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNetworkedMultiplayerENet_is_always_ordered #-}

instance Method "is_always_ordered" GodotNetworkedMultiplayerENet
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindNetworkedMultiplayerENet_is_always_ordered
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGDNativeLibrary = GodotGDNativeLibrary GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotGDNativeLibrary where
        type BaseClass GodotGDNativeLibrary = GodotResource
        super = coerce
bindGDNativeLibrary_get_config_file
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "get_config_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_get_config_file #-}

instance Method "get_config_file" GodotGDNativeLibrary
           (IO GodotConfigFile)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_get_config_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_set_config_file
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "set_config_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_set_config_file #-}

instance Method "set_config_file" GodotGDNativeLibrary
           (GodotConfigFile -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_set_config_file
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_get_current_library_path
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "get_current_library_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_get_current_library_path #-}

instance Method "get_current_library_path" GodotGDNativeLibrary
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_get_current_library_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_get_current_dependencies
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "get_current_dependencies" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_get_current_dependencies #-}

instance Method "get_current_dependencies" GodotGDNativeLibrary
           (IO GodotPoolStringArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_get_current_dependencies
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_should_load_once
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "should_load_once" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_should_load_once #-}

instance Method "should_load_once" GodotGDNativeLibrary (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_should_load_once
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_is_singleton
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "is_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_is_singleton #-}

instance Method "is_singleton" GodotGDNativeLibrary (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_is_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_get_symbol_prefix
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "get_symbol_prefix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_get_symbol_prefix #-}

instance Method "get_symbol_prefix" GodotGDNativeLibrary
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_get_symbol_prefix
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_is_reloadable
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "is_reloadable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_is_reloadable #-}

instance Method "is_reloadable" GodotGDNativeLibrary (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_is_reloadable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_set_load_once
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "set_load_once" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_set_load_once #-}

instance Method "set_load_once" GodotGDNativeLibrary
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_set_load_once
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_set_singleton
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "set_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_set_singleton #-}

instance Method "set_singleton" GodotGDNativeLibrary
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_set_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_set_symbol_prefix
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "set_symbol_prefix" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_set_symbol_prefix #-}

instance Method "set_symbol_prefix" GodotGDNativeLibrary
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_set_symbol_prefix
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNativeLibrary_set_reloadable
  = unsafePerformIO $
      withCString "GDNativeLibrary" $
        \ clsNamePtr ->
          withCString "set_reloadable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNativeLibrary_set_reloadable #-}

instance Method "set_reloadable" GodotGDNativeLibrary
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNativeLibrary_set_reloadable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGDNative = GodotGDNative GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotGDNative where
        type BaseClass GodotGDNative = GodotReference
        super = coerce
bindGDNative_set_library
  = unsafePerformIO $
      withCString "GDNative" $
        \ clsNamePtr ->
          withCString "set_library" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNative_set_library #-}

instance Method "set_library" GodotGDNative
           (GodotGDNativeLibrary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNative_set_library (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNative_get_library
  = unsafePerformIO $
      withCString "GDNative" $
        \ clsNamePtr ->
          withCString "get_library" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNative_get_library #-}

instance Method "get_library" GodotGDNative
           (IO GodotGDNativeLibrary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNative_get_library (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNative_initialize
  = unsafePerformIO $
      withCString "GDNative" $
        \ clsNamePtr ->
          withCString "initialize" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNative_initialize #-}

instance Method "initialize" GodotGDNative (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNative_initialize (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNative_terminate
  = unsafePerformIO $
      withCString "GDNative" $
        \ clsNamePtr ->
          withCString "terminate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNative_terminate #-}

instance Method "terminate" GodotGDNative (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNative_terminate (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDNative_call_native
  = unsafePerformIO $
      withCString "GDNative" $
        \ clsNamePtr ->
          withCString "call_native" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDNative_call_native #-}

instance Method "call_native" GodotGDNative
           (GodotString -> GodotString -> GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDNative_call_native (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMultiplayerPeerGDNative = GodotMultiplayerPeerGDNative GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotMultiplayerPeerGDNative where
        type BaseClass GodotMultiplayerPeerGDNative =
             GodotNetworkedMultiplayerPeer
        super = coerce

newtype GodotPacketPeerGDNative = GodotPacketPeerGDNative GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotPacketPeerGDNative where
        type BaseClass GodotPacketPeerGDNative = GodotPacketPeer
        super = coerce

newtype GodotStreamPeerGDNative = GodotStreamPeerGDNative GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotStreamPeerGDNative where
        type BaseClass GodotStreamPeerGDNative = GodotStreamPeer
        super = coerce

newtype GodotARVRInterfaceGDNative = GodotARVRInterfaceGDNative GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotARVRInterfaceGDNative where
        type BaseClass GodotARVRInterfaceGDNative = GodotARVRInterface
        super = coerce

newtype GodotNativeScript = GodotNativeScript GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotNativeScript where
        type BaseClass GodotNativeScript = GodotScript
        super = coerce
bindNativeScript_set_class_name
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "set_class_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_set_class_name #-}

instance Method "set_class_name" GodotNativeScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_set_class_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_class_name
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_class_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_class_name #-}

instance Method "get_class_name" GodotNativeScript (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_class_name (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_set_library
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "set_library" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_set_library #-}

instance Method "set_library" GodotNativeScript
           (GodotGDNativeLibrary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_set_library (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_library
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_library" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_library #-}

instance Method "get_library" GodotNativeScript
           (IO GodotGDNativeLibrary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_library (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_set_script_class_name
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "set_script_class_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_set_script_class_name #-}

instance Method "set_script_class_name" GodotNativeScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_set_script_class_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_script_class_name
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_script_class_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_script_class_name #-}

instance Method "get_script_class_name" GodotNativeScript
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_script_class_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_set_script_class_icon_path
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "set_script_class_icon_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_set_script_class_icon_path #-}

instance Method "set_script_class_icon_path" GodotNativeScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_set_script_class_icon_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_script_class_icon_path
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_script_class_icon_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_script_class_icon_path #-}

instance Method "get_script_class_icon_path" GodotNativeScript
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_script_class_icon_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_class_documentation
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_class_documentation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_class_documentation #-}

instance Method "get_class_documentation" GodotNativeScript
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_class_documentation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_method_documentation
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_method_documentation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_method_documentation #-}

instance Method "get_method_documentation" GodotNativeScript
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_method_documentation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_signal_documentation
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_signal_documentation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_signal_documentation #-}

instance Method "get_signal_documentation" GodotNativeScript
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_signal_documentation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNativeScript_get_property_documentation
  = unsafePerformIO $
      withCString "NativeScript" $
        \ clsNamePtr ->
          withCString "get_property_documentation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNativeScript_get_property_documentation #-}

instance Method "get_property_documentation" GodotNativeScript
           (GodotString -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNativeScript_get_property_documentation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotPluginScript = GodotPluginScript GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotPluginScript where
        type BaseClass GodotPluginScript = GodotScript
        super = coerce

newtype GodotGDScript = GodotGDScript GodotObject
                          deriving newtype AsVariant

instance HasBaseClass GodotGDScript where
        type BaseClass GodotGDScript = GodotScript
        super = coerce
bindGDScript_get_as_byte_code
  = unsafePerformIO $
      withCString "GDScript" $
        \ clsNamePtr ->
          withCString "get_as_byte_code" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDScript_get_as_byte_code #-}

instance Method "get_as_byte_code" GodotGDScript
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDScript_get_as_byte_code (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGDScriptFunctionState = GodotGDScriptFunctionState GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotGDScriptFunctionState where
        type BaseClass GodotGDScriptFunctionState = GodotReference
        super = coerce
bindGDScriptFunctionState_resume
  = unsafePerformIO $
      withCString "GDScriptFunctionState" $
        \ clsNamePtr ->
          withCString "resume" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDScriptFunctionState_resume #-}

instance Method "resume" GodotGDScriptFunctionState
           (GodotVariant -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDScriptFunctionState_resume
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGDScriptFunctionState_is_valid
  = unsafePerformIO $
      withCString "GDScriptFunctionState" $
        \ clsNamePtr ->
          withCString "is_valid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGDScriptFunctionState_is_valid #-}

instance Method "is_valid" GodotGDScriptFunctionState
           (Bool -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGDScriptFunctionState_is_valid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotGridMap = GodotGridMap GodotObject
                         deriving newtype AsVariant

instance HasBaseClass GodotGridMap where
        type BaseClass GodotGridMap = GodotSpatial
        super = coerce
bindGridMap_set_collision_layer
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_collision_layer #-}

instance Method "set_collision_layer" GodotGridMap (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_collision_layer
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_collision_layer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_collision_layer #-}

instance Method "get_collision_layer" GodotGridMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_collision_layer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_collision_mask
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_collision_mask #-}

instance Method "set_collision_mask" GodotGridMap (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_collision_mask
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_collision_mask" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_collision_mask #-}

instance Method "get_collision_mask" GodotGridMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_collision_mask (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_collision_mask_bit
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_collision_mask_bit #-}

instance Method "set_collision_mask_bit" GodotGridMap
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_collision_mask_bit
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_collision_mask_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_collision_mask_bit #-}

instance Method "get_collision_mask_bit" GodotGridMap
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_collision_mask_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_collision_layer_bit
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_collision_layer_bit #-}

instance Method "set_collision_layer_bit" GodotGridMap
           (Int -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_collision_layer_bit
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_collision_layer_bit" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_collision_layer_bit #-}

instance Method "get_collision_layer_bit" GodotGridMap
           (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_collision_layer_bit
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_theme
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_theme" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_theme #-}

instance Method "set_theme" GodotGridMap
           (GodotMeshLibrary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_theme (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_theme
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_theme" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_theme #-}

instance Method "get_theme" GodotGridMap (IO GodotMeshLibrary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_theme (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_mesh_library
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_mesh_library" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_mesh_library #-}

instance Method "set_mesh_library" GodotGridMap
           (GodotMeshLibrary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_mesh_library (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_mesh_library
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_mesh_library" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_mesh_library #-}

instance Method "get_mesh_library" GodotGridMap
           (IO GodotMeshLibrary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_mesh_library (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_cell_size
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_cell_size #-}

instance Method "set_cell_size" GodotGridMap
           (GodotVector3 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_cell_size
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_cell_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_cell_size #-}

instance Method "get_cell_size" GodotGridMap (IO GodotVector3)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_cell_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_cell_scale
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_cell_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_cell_scale #-}

instance Method "set_cell_scale" GodotGridMap (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_cell_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_cell_scale
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_cell_scale" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_cell_scale #-}

instance Method "get_cell_scale" GodotGridMap (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_cell_scale (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_octant_size
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_octant_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_octant_size #-}

instance Method "set_octant_size" GodotGridMap (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_octant_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_octant_size
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_octant_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_octant_size #-}

instance Method "get_octant_size" GodotGridMap (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_octant_size (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_cell_item
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_cell_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_cell_item #-}

instance Method "set_cell_item" GodotGridMap
           (Int -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_cell_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_cell_item
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_cell_item" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_cell_item #-}

instance Method "get_cell_item" GodotGridMap
           (Int -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_cell_item (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_cell_item_orientation
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_cell_item_orientation" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_cell_item_orientation #-}

instance Method "get_cell_item_orientation" GodotGridMap
           (Int -> Int -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_cell_item_orientation
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_world_to_map
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "world_to_map" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_world_to_map #-}

instance Method "world_to_map" GodotGridMap
           (GodotVector3 -> IO GodotVector3)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_world_to_map (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_map_to_world
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "map_to_world" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_map_to_world #-}

instance Method "map_to_world" GodotGridMap
           (Int -> Int -> Int -> IO GodotVector3)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_map_to_world (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap__update_octants_callback
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "_update_octants_callback" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap__update_octants_callback #-}

instance Method "_update_octants_callback" GodotGridMap (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap__update_octants_callback
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_resource_changed
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "resource_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_resource_changed #-}

instance Method "resource_changed" GodotGridMap
           (GodotResource -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_resource_changed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_center_x
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_center_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_center_x #-}

instance Method "set_center_x" GodotGridMap (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_center_x (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_center_x
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_center_x" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_center_x #-}

instance Method "get_center_x" GodotGridMap (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_center_x (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_center_y
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_center_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_center_y #-}

instance Method "set_center_y" GodotGridMap (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_center_y (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_center_y
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_center_y" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_center_y #-}

instance Method "get_center_y" GodotGridMap (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_center_y (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_center_z
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_center_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_center_z #-}

instance Method "set_center_z" GodotGridMap (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_center_z (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_center_z
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_center_z" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_center_z #-}

instance Method "get_center_z" GodotGridMap (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_center_z (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_set_clip
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "set_clip" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_set_clip #-}

instance Method "set_clip" GodotGridMap
           (Bool -> Bool -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_set_clip (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_clear
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_clear #-}

instance Method "clear" GodotGridMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_clear (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_used_cells
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_used_cells" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_used_cells #-}

instance Method "get_used_cells" GodotGridMap (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_used_cells (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_meshes
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_meshes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_meshes #-}

instance Method "get_meshes" GodotGridMap (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_meshes (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_bake_meshes
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_bake_meshes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_bake_meshes #-}

instance Method "get_bake_meshes" GodotGridMap (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_bake_meshes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_get_bake_mesh_instance
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "get_bake_mesh_instance" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_get_bake_mesh_instance #-}

instance Method "get_bake_mesh_instance" GodotGridMap
           (Int -> IO GodotRid)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_get_bake_mesh_instance
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_clear_baked_meshes
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "clear_baked_meshes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_clear_baked_meshes #-}

instance Method "clear_baked_meshes" GodotGridMap (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_clear_baked_meshes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindGridMap_make_baked_meshes
  = unsafePerformIO $
      withCString "GridMap" $
        \ clsNamePtr ->
          withCString "make_baked_meshes" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindGridMap_make_baked_meshes #-}

instance Method "make_baked_meshes" GodotGridMap
           (Bool -> Float -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindGridMap_make_baked_meshes (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotMobileVRInterface = GodotMobileVRInterface GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotMobileVRInterface where
        type BaseClass GodotMobileVRInterface = GodotARVRInterface
        super = coerce
bindMobileVRInterface_set_iod
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "set_iod" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_set_iod #-}

instance Method "set_iod" GodotMobileVRInterface (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_set_iod (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_get_iod
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "get_iod" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_get_iod #-}

instance Method "get_iod" GodotMobileVRInterface (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_get_iod (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_set_display_width
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "set_display_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_set_display_width #-}

instance Method "set_display_width" GodotMobileVRInterface
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_set_display_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_get_display_width
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "get_display_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_get_display_width #-}

instance Method "get_display_width" GodotMobileVRInterface
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_get_display_width
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_set_display_to_lens
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "set_display_to_lens" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_set_display_to_lens #-}

instance Method "set_display_to_lens" GodotMobileVRInterface
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_set_display_to_lens
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_get_display_to_lens
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "get_display_to_lens" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_get_display_to_lens #-}

instance Method "get_display_to_lens" GodotMobileVRInterface
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_get_display_to_lens
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_set_oversample
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "set_oversample" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_set_oversample #-}

instance Method "set_oversample" GodotMobileVRInterface
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_set_oversample
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_get_oversample
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "get_oversample" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_get_oversample #-}

instance Method "get_oversample" GodotMobileVRInterface (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_get_oversample
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_set_k1
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "set_k1" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_set_k1 #-}

instance Method "set_k1" GodotMobileVRInterface (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_set_k1 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_get_k1
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "get_k1" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_get_k1 #-}

instance Method "get_k1" GodotMobileVRInterface (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_get_k1 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_set_k2
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "set_k2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_set_k2 #-}

instance Method "set_k2" GodotMobileVRInterface (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_set_k2 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindMobileVRInterface_get_k2
  = unsafePerformIO $
      withCString "MobileVRInterface" $
        \ clsNamePtr ->
          withCString "get_k2" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindMobileVRInterface_get_k2 #-}

instance Method "get_k2" GodotMobileVRInterface (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindMobileVRInterface_get_k2 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotOpenSimplexNoise = GodotOpenSimplexNoise GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotOpenSimplexNoise where
        type BaseClass GodotOpenSimplexNoise = GodotResource
        super = coerce
bindOpenSimplexNoise_get_seed
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_seed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_seed #-}

instance Method "get_seed" GodotOpenSimplexNoise (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_seed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_set_seed
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "set_seed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_set_seed #-}

instance Method "set_seed" GodotOpenSimplexNoise (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_set_seed (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_set_octaves
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "set_octaves" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_set_octaves #-}

instance Method "set_octaves" GodotOpenSimplexNoise (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_set_octaves
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_octaves
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_octaves" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_octaves #-}

instance Method "get_octaves" GodotOpenSimplexNoise (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_octaves
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_set_period
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "set_period" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_set_period #-}

instance Method "set_period" GodotOpenSimplexNoise (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_set_period (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_period
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_period" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_period #-}

instance Method "get_period" GodotOpenSimplexNoise (IO Float) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_period (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_set_persistence
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "set_persistence" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_set_persistence #-}

instance Method "set_persistence" GodotOpenSimplexNoise
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_set_persistence
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_persistence
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_persistence" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_persistence #-}

instance Method "get_persistence" GodotOpenSimplexNoise (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_persistence
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_set_lacunarity
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "set_lacunarity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_set_lacunarity #-}

instance Method "set_lacunarity" GodotOpenSimplexNoise
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_set_lacunarity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_lacunarity
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_lacunarity" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_lacunarity #-}

instance Method "get_lacunarity" GodotOpenSimplexNoise (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_lacunarity
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_image
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_image" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_image #-}

instance Method "get_image" GodotOpenSimplexNoise
           (Int -> Int -> IO GodotImage)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_image (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_seamless_image
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_seamless_image" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_seamless_image #-}

instance Method "get_seamless_image" GodotOpenSimplexNoise
           (Int -> IO GodotImage)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_seamless_image
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_noise_2d
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_noise_2d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_noise_2d #-}

instance Method "get_noise_2d" GodotOpenSimplexNoise
           (Float -> Float -> IO Float)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_noise_2d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_noise_3d
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_noise_3d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_noise_3d #-}

instance Method "get_noise_3d" GodotOpenSimplexNoise
           (Float -> Float -> Float -> IO Float)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_noise_3d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_noise_4d
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_noise_4d" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_noise_4d #-}

instance Method "get_noise_4d" GodotOpenSimplexNoise
           (Float -> Float -> Float -> Float -> IO Float)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_noise_4d
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_noise_2dv
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_noise_2dv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_noise_2dv #-}

instance Method "get_noise_2dv" GodotOpenSimplexNoise
           (GodotVector2 -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_noise_2dv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindOpenSimplexNoise_get_noise_3dv
  = unsafePerformIO $
      withCString "OpenSimplexNoise" $
        \ clsNamePtr ->
          withCString "get_noise_3dv" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindOpenSimplexNoise_get_noise_3dv #-}

instance Method "get_noise_3dv" GodotOpenSimplexNoise
           (GodotVector3 -> IO Float)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindOpenSimplexNoise_get_noise_3dv
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotNoiseTexture = GodotNoiseTexture GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotNoiseTexture where
        type BaseClass GodotNoiseTexture = GodotTexture
        super = coerce
bindNoiseTexture_get_width
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "get_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_get_width #-}

instance Method "get_width" GodotNoiseTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_get_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_get_height
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "get_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_get_height #-}

instance Method "get_height" GodotNoiseTexture (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_get_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_set_width
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "set_width" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_set_width #-}

instance Method "set_width" GodotNoiseTexture (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_set_width (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_set_height
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "set_height" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_set_height #-}

instance Method "set_height" GodotNoiseTexture (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_set_height (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_set_noise
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "set_noise" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_set_noise #-}

instance Method "set_noise" GodotNoiseTexture
           (GodotOpenSimplexNoise -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_set_noise (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_get_noise
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "get_noise" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_get_noise #-}

instance Method "get_noise" GodotNoiseTexture
           (IO GodotOpenSimplexNoise)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_get_noise (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_set_seamless
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "set_seamless" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_set_seamless #-}

instance Method "set_seamless" GodotNoiseTexture (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_set_seamless (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_get_seamless
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "get_seamless" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_get_seamless #-}

instance Method "get_seamless" GodotNoiseTexture (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_get_seamless (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_set_as_normalmap
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "set_as_normalmap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_set_as_normalmap #-}

instance Method "set_as_normalmap" GodotNoiseTexture
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_set_as_normalmap
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture_is_normalmap
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "is_normalmap" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture_is_normalmap #-}

instance Method "is_normalmap" GodotNoiseTexture (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture_is_normalmap (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture__update_texture
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "_update_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture__update_texture #-}

instance Method "_update_texture" GodotNoiseTexture (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture__update_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture__generate_texture
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "_generate_texture" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture__generate_texture #-}

instance Method "_generate_texture" GodotNoiseTexture
           (IO GodotImage)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture__generate_texture
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindNoiseTexture__thread_done
  = unsafePerformIO $
      withCString "NoiseTexture" $
        \ clsNamePtr ->
          withCString "_thread_done" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindNoiseTexture__thread_done #-}

instance Method "_thread_done" GodotNoiseTexture
           (GodotImage -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindNoiseTexture__thread_done (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRegExMatch = GodotRegExMatch GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotRegExMatch where
        type BaseClass GodotRegExMatch = GodotReference
        super = coerce
bindRegExMatch_get_subject
  = unsafePerformIO $
      withCString "RegExMatch" $
        \ clsNamePtr ->
          withCString "get_subject" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegExMatch_get_subject #-}

instance Method "get_subject" GodotRegExMatch (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegExMatch_get_subject (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegExMatch_get_group_count
  = unsafePerformIO $
      withCString "RegExMatch" $
        \ clsNamePtr ->
          withCString "get_group_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegExMatch_get_group_count #-}

instance Method "get_group_count" GodotRegExMatch (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegExMatch_get_group_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegExMatch_get_names
  = unsafePerformIO $
      withCString "RegExMatch" $
        \ clsNamePtr ->
          withCString "get_names" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegExMatch_get_names #-}

instance Method "get_names" GodotRegExMatch (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegExMatch_get_names (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegExMatch_get_strings
  = unsafePerformIO $
      withCString "RegExMatch" $
        \ clsNamePtr ->
          withCString "get_strings" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegExMatch_get_strings #-}

instance Method "get_strings" GodotRegExMatch (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegExMatch_get_strings (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegExMatch_get_string
  = unsafePerformIO $
      withCString "RegExMatch" $
        \ clsNamePtr ->
          withCString "get_string" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegExMatch_get_string #-}

instance Method "get_string" GodotRegExMatch
           (GodotVariant -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegExMatch_get_string (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegExMatch_get_start
  = unsafePerformIO $
      withCString "RegExMatch" $
        \ clsNamePtr ->
          withCString "get_start" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegExMatch_get_start #-}

instance Method "get_start" GodotRegExMatch
           (GodotVariant -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegExMatch_get_start (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegExMatch_get_end
  = unsafePerformIO $
      withCString "RegExMatch" $
        \ clsNamePtr ->
          withCString "get_end" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegExMatch_get_end #-}

instance Method "get_end" GodotRegExMatch (GodotVariant -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegExMatch_get_end (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotRegEx = GodotRegEx GodotObject
                       deriving newtype AsVariant

instance HasBaseClass GodotRegEx where
        type BaseClass GodotRegEx = GodotReference
        super = coerce
bindRegEx_clear
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "clear" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_clear #-}

instance Method "clear" GodotRegEx (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_clear (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_compile
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "compile" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_compile #-}

instance Method "compile" GodotRegEx (GodotString -> IO Int) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_compile (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_search
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "search" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_search #-}

instance Method "search" GodotRegEx
           (GodotString -> Int -> Int -> IO GodotRegExMatch)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_search (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_search_all
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "search_all" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_search_all #-}

instance Method "search_all" GodotRegEx
           (GodotString -> Int -> Int -> IO GodotArray)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_search_all (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_sub
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "sub" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_sub #-}

instance Method "sub" GodotRegEx
           (GodotString ->
              GodotString -> Bool -> Int -> Int -> IO GodotString)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_sub (coerce cls) arrPtr len >>=
                   \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_is_valid
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "is_valid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_is_valid #-}

instance Method "is_valid" GodotRegEx (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_is_valid (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_get_pattern
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "get_pattern" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_get_pattern #-}

instance Method "get_pattern" GodotRegEx (IO GodotString) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_get_pattern (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_get_group_count
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "get_group_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_get_group_count #-}

instance Method "get_group_count" GodotRegEx (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_get_group_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindRegEx_get_names
  = unsafePerformIO $
      withCString "RegEx" $
        \ clsNamePtr ->
          withCString "get_names" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindRegEx_get_names #-}

instance Method "get_names" GodotRegEx (IO GodotArray) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindRegEx_get_names (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotResourceImporterOGGVorbis = GodotResourceImporterOGGVorbis GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotResourceImporterOGGVorbis where
        type BaseClass GodotResourceImporterOGGVorbis =
             GodotResourceImporter
        super = coerce

newtype GodotResourceImporter = GodotResourceImporter GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotResourceImporter where
        type BaseClass GodotResourceImporter = GodotReference
        super = coerce

newtype GodotAudioStreamOGGVorbis = GodotAudioStreamOGGVorbis GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotAudioStreamOGGVorbis where
        type BaseClass GodotAudioStreamOGGVorbis = GodotAudioStream
        super = coerce
bindAudioStreamOGGVorbis_set_data
  = unsafePerformIO $
      withCString "AudioStreamOGGVorbis" $
        \ clsNamePtr ->
          withCString "set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamOGGVorbis_set_data #-}

instance Method "set_data" GodotAudioStreamOGGVorbis
           (GodotPoolByteArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamOGGVorbis_set_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamOGGVorbis_get_data
  = unsafePerformIO $
      withCString "AudioStreamOGGVorbis" $
        \ clsNamePtr ->
          withCString "get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamOGGVorbis_get_data #-}

instance Method "get_data" GodotAudioStreamOGGVorbis
           (IO GodotPoolByteArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamOGGVorbis_get_data
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamOGGVorbis_set_loop
  = unsafePerformIO $
      withCString "AudioStreamOGGVorbis" $
        \ clsNamePtr ->
          withCString "set_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamOGGVorbis_set_loop #-}

instance Method "set_loop" GodotAudioStreamOGGVorbis
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamOGGVorbis_set_loop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamOGGVorbis_has_loop
  = unsafePerformIO $
      withCString "AudioStreamOGGVorbis" $
        \ clsNamePtr ->
          withCString "has_loop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamOGGVorbis_has_loop #-}

instance Method "has_loop" GodotAudioStreamOGGVorbis (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamOGGVorbis_has_loop
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamOGGVorbis_set_loop_offset
  = unsafePerformIO $
      withCString "AudioStreamOGGVorbis" $
        \ clsNamePtr ->
          withCString "set_loop_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamOGGVorbis_set_loop_offset #-}

instance Method "set_loop_offset" GodotAudioStreamOGGVorbis
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamOGGVorbis_set_loop_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindAudioStreamOGGVorbis_get_loop_offset
  = unsafePerformIO $
      withCString "AudioStreamOGGVorbis" $
        \ clsNamePtr ->
          withCString "get_loop_offset" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindAudioStreamOGGVorbis_get_loop_offset #-}

instance Method "get_loop_offset" GodotAudioStreamOGGVorbis
           (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindAudioStreamOGGVorbis_get_loop_offset
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVideoStreamTheora = GodotVideoStreamTheora GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotVideoStreamTheora where
        type BaseClass GodotVideoStreamTheora = GodotVideoStream
        super = coerce
bindVideoStreamTheora_set_file
  = unsafePerformIO $
      withCString "VideoStreamTheora" $
        \ clsNamePtr ->
          withCString "set_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoStreamTheora_set_file #-}

instance Method "set_file" GodotVideoStreamTheora
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoStreamTheora_set_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoStreamTheora_get_file
  = unsafePerformIO $
      withCString "VideoStreamTheora" $
        \ clsNamePtr ->
          withCString "get_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoStreamTheora_get_file #-}

instance Method "get_file" GodotVideoStreamTheora (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoStreamTheora_get_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotUPNP = GodotUPNP GodotObject
                      deriving newtype AsVariant

instance HasBaseClass GodotUPNP where
        type BaseClass GodotUPNP = GodotReference
        super = coerce
bindUPNP_get_device_count
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "get_device_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_get_device_count #-}

instance Method "get_device_count" GodotUPNP (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_get_device_count (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_get_device
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "get_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_get_device #-}

instance Method "get_device" GodotUPNP (Int -> IO GodotUPNPDevice)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_get_device (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_add_device
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "add_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_add_device #-}

instance Method "add_device" GodotUPNP (GodotUPNPDevice -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_add_device (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_set_device
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "set_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_set_device #-}

instance Method "set_device" GodotUPNP
           (Int -> GodotUPNPDevice -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_set_device (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_remove_device
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "remove_device" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_remove_device #-}

instance Method "remove_device" GodotUPNP (Int -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_remove_device (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_clear_devices
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "clear_devices" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_clear_devices #-}

instance Method "clear_devices" GodotUPNP (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_clear_devices (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_get_gateway
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "get_gateway" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_get_gateway #-}

instance Method "get_gateway" GodotUPNP (IO GodotUPNPDevice) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_get_gateway (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_discover
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "discover" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_discover #-}

instance Method "discover" GodotUPNP
           (Int -> Int -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_discover (coerce cls) arrPtr len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_query_external_address
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "query_external_address" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_query_external_address #-}

instance Method "query_external_address" GodotUPNP (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_query_external_address (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_add_port_mapping
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "add_port_mapping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_add_port_mapping #-}

instance Method "add_port_mapping" GodotUPNP
           (Int -> Int -> GodotString -> GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_add_port_mapping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_delete_port_mapping
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "delete_port_mapping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_delete_port_mapping #-}

instance Method "delete_port_mapping" GodotUPNP
           (Int -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_delete_port_mapping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_set_discover_multicast_if
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "set_discover_multicast_if" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_set_discover_multicast_if #-}

instance Method "set_discover_multicast_if" GodotUPNP
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_set_discover_multicast_if
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_get_discover_multicast_if
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "get_discover_multicast_if" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_get_discover_multicast_if #-}

instance Method "get_discover_multicast_if" GodotUPNP
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_get_discover_multicast_if
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_set_discover_local_port
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "set_discover_local_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_set_discover_local_port #-}

instance Method "set_discover_local_port" GodotUPNP (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_set_discover_local_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_get_discover_local_port
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "get_discover_local_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_get_discover_local_port #-}

instance Method "get_discover_local_port" GodotUPNP (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_get_discover_local_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_set_discover_ipv6
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "set_discover_ipv6" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_set_discover_ipv6 #-}

instance Method "set_discover_ipv6" GodotUPNP (Bool -> IO ()) where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_set_discover_ipv6 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNP_is_discover_ipv6
  = unsafePerformIO $
      withCString "UPNP" $
        \ clsNamePtr ->
          withCString "is_discover_ipv6" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNP_is_discover_ipv6 #-}

instance Method "is_discover_ipv6" GodotUPNP (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNP_is_discover_ipv6 (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotUPNPDevice = GodotUPNPDevice GodotObject
                            deriving newtype AsVariant

instance HasBaseClass GodotUPNPDevice where
        type BaseClass GodotUPNPDevice = GodotReference
        super = coerce
bindUPNPDevice_is_valid_gateway
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "is_valid_gateway" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_is_valid_gateway #-}

instance Method "is_valid_gateway" GodotUPNPDevice (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_is_valid_gateway (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_query_external_address
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "query_external_address" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_query_external_address #-}

instance Method "query_external_address" GodotUPNPDevice
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_query_external_address
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_add_port_mapping
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "add_port_mapping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_add_port_mapping #-}

instance Method "add_port_mapping" GodotUPNPDevice
           (Int -> Int -> GodotString -> GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_add_port_mapping (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_delete_port_mapping
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "delete_port_mapping" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_delete_port_mapping #-}

instance Method "delete_port_mapping" GodotUPNPDevice
           (Int -> GodotString -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_delete_port_mapping
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_set_description_url
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "set_description_url" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_set_description_url #-}

instance Method "set_description_url" GodotUPNPDevice
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_set_description_url
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_get_description_url
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "get_description_url" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_get_description_url #-}

instance Method "get_description_url" GodotUPNPDevice
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_get_description_url
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_set_service_type
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "set_service_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_set_service_type #-}

instance Method "set_service_type" GodotUPNPDevice
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_set_service_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_get_service_type
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "get_service_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_get_service_type #-}

instance Method "get_service_type" GodotUPNPDevice (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_get_service_type (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_set_igd_control_url
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "set_igd_control_url" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_set_igd_control_url #-}

instance Method "set_igd_control_url" GodotUPNPDevice
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_set_igd_control_url
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_get_igd_control_url
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "get_igd_control_url" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_get_igd_control_url #-}

instance Method "get_igd_control_url" GodotUPNPDevice
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_get_igd_control_url
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_set_igd_service_type
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "set_igd_service_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_set_igd_service_type #-}

instance Method "set_igd_service_type" GodotUPNPDevice
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_set_igd_service_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_get_igd_service_type
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "get_igd_service_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_get_igd_service_type #-}

instance Method "get_igd_service_type" GodotUPNPDevice
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_get_igd_service_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_set_igd_our_addr
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "set_igd_our_addr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_set_igd_our_addr #-}

instance Method "set_igd_our_addr" GodotUPNPDevice
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_set_igd_our_addr (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_get_igd_our_addr
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "get_igd_our_addr" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_get_igd_our_addr #-}

instance Method "get_igd_our_addr" GodotUPNPDevice (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_get_igd_our_addr (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_set_igd_status
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "set_igd_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_set_igd_status #-}

instance Method "set_igd_status" GodotUPNPDevice (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_set_igd_status (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindUPNPDevice_get_igd_status
  = unsafePerformIO $
      withCString "UPNPDevice" $
        \ clsNamePtr ->
          withCString "get_igd_status" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindUPNPDevice_get_igd_status #-}

instance Method "get_igd_status" GodotUPNPDevice (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindUPNPDevice_get_igd_status (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScript = GodotVisualScript GodotObject
                              deriving newtype AsVariant

instance HasBaseClass GodotVisualScript where
        type BaseClass GodotVisualScript = GodotScript
        super = coerce
bindVisualScript__node_ports_changed
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "_node_ports_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript__node_ports_changed #-}

instance Method "_node_ports_changed" GodotVisualScript
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript__node_ports_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_add_function
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "add_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_add_function #-}

instance Method "add_function" GodotVisualScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_add_function (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_has_function
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "has_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_has_function #-}

instance Method "has_function" GodotVisualScript
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_has_function (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_remove_function
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "remove_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_remove_function #-}

instance Method "remove_function" GodotVisualScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_remove_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_rename_function
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "rename_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_rename_function #-}

instance Method "rename_function" GodotVisualScript
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_rename_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_set_function_scroll
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "set_function_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_set_function_scroll #-}

instance Method "set_function_scroll" GodotVisualScript
           (GodotString -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_set_function_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_get_function_scroll
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "get_function_scroll" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_get_function_scroll #-}

instance Method "get_function_scroll" GodotVisualScript
           (GodotString -> IO GodotVector2)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_get_function_scroll
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_add_node
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "add_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_add_node #-}

instance Method "add_node" GodotVisualScript
           (GodotString ->
              Int -> GodotVisualScriptNode -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_add_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_remove_node
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "remove_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_remove_node #-}

instance Method "remove_node" GodotVisualScript
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_remove_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_get_function_node_id
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "get_function_node_id" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_get_function_node_id #-}

instance Method "get_function_node_id" GodotVisualScript
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_get_function_node_id
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_get_node
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "get_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_get_node #-}

instance Method "get_node" GodotVisualScript
           (GodotString -> Int -> IO GodotVisualScriptNode)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_get_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_has_node
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "has_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_has_node #-}

instance Method "has_node" GodotVisualScript
           (GodotString -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_has_node (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_set_node_position
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "set_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_set_node_position #-}

instance Method "set_node_position" GodotVisualScript
           (GodotString -> Int -> GodotVector2 -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_set_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_get_node_position
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "get_node_position" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_get_node_position #-}

instance Method "get_node_position" GodotVisualScript
           (GodotString -> Int -> IO GodotVector2)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_get_node_position
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_sequence_connect
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "sequence_connect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_sequence_connect #-}

instance Method "sequence_connect" GodotVisualScript
           (GodotString -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_sequence_connect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_sequence_disconnect
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "sequence_disconnect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_sequence_disconnect #-}

instance Method "sequence_disconnect" GodotVisualScript
           (GodotString -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_sequence_disconnect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_has_sequence_connection
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "has_sequence_connection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_has_sequence_connection #-}

instance Method "has_sequence_connection" GodotVisualScript
           (GodotString -> Int -> Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_has_sequence_connection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_data_connect
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "data_connect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_data_connect #-}

instance Method "data_connect" GodotVisualScript
           (GodotString -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_data_connect (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_data_disconnect
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "data_disconnect" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_data_disconnect #-}

instance Method "data_disconnect" GodotVisualScript
           (GodotString -> Int -> Int -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_data_disconnect
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_has_data_connection
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "has_data_connection" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_has_data_connection #-}

instance Method "has_data_connection" GodotVisualScript
           (GodotString -> Int -> Int -> Int -> Int -> IO Bool)
         where
        runMethod cls arg1 arg2 arg3 arg4 arg5
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4,
               toVariant arg5]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_has_data_connection
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_add_variable
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "add_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_add_variable #-}

instance Method "add_variable" GodotVisualScript
           (GodotString -> GodotVariant -> Bool -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_add_variable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_has_variable
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "has_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_has_variable #-}

instance Method "has_variable" GodotVisualScript
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_has_variable (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_remove_variable
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "remove_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_remove_variable #-}

instance Method "remove_variable" GodotVisualScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_remove_variable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_set_variable_default_value
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "set_variable_default_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_set_variable_default_value #-}

instance Method "set_variable_default_value" GodotVisualScript
           (GodotString -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_set_variable_default_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_get_variable_default_value
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "get_variable_default_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_get_variable_default_value #-}

instance Method "get_variable_default_value" GodotVisualScript
           (GodotString -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_get_variable_default_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_set_variable_info
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "set_variable_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_set_variable_info #-}

instance Method "set_variable_info" GodotVisualScript
           (GodotString -> GodotDictionary -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_set_variable_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_get_variable_info
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "get_variable_info" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_get_variable_info #-}

instance Method "get_variable_info" GodotVisualScript
           (GodotString -> IO GodotDictionary)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_get_variable_info
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_set_variable_export
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "set_variable_export" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_set_variable_export #-}

instance Method "set_variable_export" GodotVisualScript
           (GodotString -> Bool -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_set_variable_export
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_get_variable_export
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "get_variable_export" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_get_variable_export #-}

instance Method "get_variable_export" GodotVisualScript
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_get_variable_export
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_rename_variable
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "rename_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_rename_variable #-}

instance Method "rename_variable" GodotVisualScript
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_rename_variable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_add_custom_signal
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "add_custom_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_add_custom_signal #-}

instance Method "add_custom_signal" GodotVisualScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_add_custom_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_has_custom_signal
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "has_custom_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_has_custom_signal #-}

instance Method "has_custom_signal" GodotVisualScript
           (GodotString -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_has_custom_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_add_argument
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_add_argument" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_add_argument #-}

instance Method "custom_signal_add_argument" GodotVisualScript
           (GodotString -> Int -> GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_custom_signal_add_argument
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_set_argument_type
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_set_argument_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_set_argument_type #-}

instance Method "custom_signal_set_argument_type" GodotVisualScript
           (GodotString -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScript_custom_signal_set_argument_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_get_argument_type
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_get_argument_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_get_argument_type #-}

instance Method "custom_signal_get_argument_type" GodotVisualScript
           (GodotString -> Int -> IO Int)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScript_custom_signal_get_argument_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_set_argument_name
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_set_argument_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_set_argument_name #-}

instance Method "custom_signal_set_argument_name" GodotVisualScript
           (GodotString -> Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScript_custom_signal_set_argument_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_get_argument_name
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_get_argument_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_get_argument_name #-}

instance Method "custom_signal_get_argument_name" GodotVisualScript
           (GodotString -> Int -> IO GodotString)
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScript_custom_signal_get_argument_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_remove_argument
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_remove_argument" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_remove_argument #-}

instance Method "custom_signal_remove_argument" GodotVisualScript
           (GodotString -> Int -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScript_custom_signal_remove_argument
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_get_argument_count
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_get_argument_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_get_argument_count #-}

instance Method "custom_signal_get_argument_count"
           GodotVisualScript
           (GodotString -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScript_custom_signal_get_argument_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_custom_signal_swap_argument
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "custom_signal_swap_argument" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_custom_signal_swap_argument #-}

instance Method "custom_signal_swap_argument" GodotVisualScript
           (GodotString -> Int -> Int -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_custom_signal_swap_argument
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_remove_custom_signal
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "remove_custom_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_remove_custom_signal #-}

instance Method "remove_custom_signal" GodotVisualScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_remove_custom_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_rename_custom_signal
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "rename_custom_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_rename_custom_signal #-}

instance Method "rename_custom_signal" GodotVisualScript
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_rename_custom_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript_set_instance_base_type
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "set_instance_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript_set_instance_base_type #-}

instance Method "set_instance_base_type" GodotVisualScript
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript_set_instance_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript__set_data
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "_set_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript__set_data #-}

instance Method "_set_data" GodotVisualScript
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript__set_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScript__get_data
  = unsafePerformIO $
      withCString "VisualScript" $
        \ clsNamePtr ->
          withCString "_get_data" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScript__get_data #-}

instance Method "_get_data" GodotVisualScript (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScript__get_data (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptNode = GodotVisualScriptNode GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptNode where
        type BaseClass GodotVisualScriptNode = GodotResource
        super = coerce
bindVisualScriptNode_get_visual_script
  = unsafePerformIO $
      withCString "VisualScriptNode" $
        \ clsNamePtr ->
          withCString "get_visual_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptNode_get_visual_script #-}

instance Method "get_visual_script" GodotVisualScriptNode
           (IO GodotVisualScript)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptNode_get_visual_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptNode_set_default_input_value
  = unsafePerformIO $
      withCString "VisualScriptNode" $
        \ clsNamePtr ->
          withCString "set_default_input_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptNode_set_default_input_value #-}

instance Method "set_default_input_value" GodotVisualScriptNode
           (Int -> GodotVariant -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptNode_set_default_input_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptNode_get_default_input_value
  = unsafePerformIO $
      withCString "VisualScriptNode" $
        \ clsNamePtr ->
          withCString "get_default_input_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptNode_get_default_input_value #-}

instance Method "get_default_input_value" GodotVisualScriptNode
           (Int -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptNode_get_default_input_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptNode_ports_changed_notify
  = unsafePerformIO $
      withCString "VisualScriptNode" $
        \ clsNamePtr ->
          withCString "ports_changed_notify" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptNode_ports_changed_notify #-}

instance Method "ports_changed_notify" GodotVisualScriptNode
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptNode_ports_changed_notify
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptNode__set_default_input_values
  = unsafePerformIO $
      withCString "VisualScriptNode" $
        \ clsNamePtr ->
          withCString "_set_default_input_values" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptNode__set_default_input_values #-}

instance Method "_set_default_input_values" GodotVisualScriptNode
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptNode__set_default_input_values
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptNode__get_default_input_values
  = unsafePerformIO $
      withCString "VisualScriptNode" $
        \ clsNamePtr ->
          withCString "_get_default_input_values" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptNode__get_default_input_values #-}

instance Method "_get_default_input_values" GodotVisualScriptNode
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptNode__get_default_input_values
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptFunctionState = GodotVisualScriptFunctionState GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptFunctionState where
        type BaseClass GodotVisualScriptFunctionState = GodotReference
        super = coerce
bindVisualScriptFunctionState_connect_to_signal
  = unsafePerformIO $
      withCString "VisualScriptFunctionState" $
        \ clsNamePtr ->
          withCString "connect_to_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionState_connect_to_signal #-}

instance Method "connect_to_signal" GodotVisualScriptFunctionState
           (GodotObject -> GodotString -> GodotArray -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptFunctionState_connect_to_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionState_resume
  = unsafePerformIO $
      withCString "VisualScriptFunctionState" $
        \ clsNamePtr ->
          withCString "resume" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionState_resume #-}

instance Method "resume" GodotVisualScriptFunctionState
           (GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionState_resume
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionState_is_valid
  = unsafePerformIO $
      withCString "VisualScriptFunctionState" $
        \ clsNamePtr ->
          withCString "is_valid" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionState_is_valid #-}

instance Method "is_valid" GodotVisualScriptFunctionState (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionState_is_valid
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptFunction = GodotVisualScriptFunction GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptFunction where
        type BaseClass GodotVisualScriptFunction = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptOperator = GodotVisualScriptOperator GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptOperator where
        type BaseClass GodotVisualScriptOperator = GodotVisualScriptNode
        super = coerce
bindVisualScriptOperator_set_operator
  = unsafePerformIO $
      withCString "VisualScriptOperator" $
        \ clsNamePtr ->
          withCString "set_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptOperator_set_operator #-}

instance Method "set_operator" GodotVisualScriptOperator
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptOperator_set_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptOperator_get_operator
  = unsafePerformIO $
      withCString "VisualScriptOperator" $
        \ clsNamePtr ->
          withCString "get_operator" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptOperator_get_operator #-}

instance Method "get_operator" GodotVisualScriptOperator (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptOperator_get_operator
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptOperator_set_typed
  = unsafePerformIO $
      withCString "VisualScriptOperator" $
        \ clsNamePtr ->
          withCString "set_typed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptOperator_set_typed #-}

instance Method "set_typed" GodotVisualScriptOperator
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptOperator_set_typed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptOperator_get_typed
  = unsafePerformIO $
      withCString "VisualScriptOperator" $
        \ clsNamePtr ->
          withCString "get_typed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptOperator_get_typed #-}

instance Method "get_typed" GodotVisualScriptOperator (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptOperator_get_typed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptVariableSet = GodotVisualScriptVariableSet GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptVariableSet where
        type BaseClass GodotVisualScriptVariableSet = GodotVisualScriptNode
        super = coerce
bindVisualScriptVariableSet_set_variable
  = unsafePerformIO $
      withCString "VisualScriptVariableSet" $
        \ clsNamePtr ->
          withCString "set_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptVariableSet_set_variable #-}

instance Method "set_variable" GodotVisualScriptVariableSet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptVariableSet_set_variable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptVariableSet_get_variable
  = unsafePerformIO $
      withCString "VisualScriptVariableSet" $
        \ clsNamePtr ->
          withCString "get_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptVariableSet_get_variable #-}

instance Method "get_variable" GodotVisualScriptVariableSet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptVariableSet_get_variable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptVariableGet = GodotVisualScriptVariableGet GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptVariableGet where
        type BaseClass GodotVisualScriptVariableGet = GodotVisualScriptNode
        super = coerce
bindVisualScriptVariableGet_set_variable
  = unsafePerformIO $
      withCString "VisualScriptVariableGet" $
        \ clsNamePtr ->
          withCString "set_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptVariableGet_set_variable #-}

instance Method "set_variable" GodotVisualScriptVariableGet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptVariableGet_set_variable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptVariableGet_get_variable
  = unsafePerformIO $
      withCString "VisualScriptVariableGet" $
        \ clsNamePtr ->
          withCString "get_variable" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptVariableGet_get_variable #-}

instance Method "get_variable" GodotVisualScriptVariableGet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptVariableGet_get_variable
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptConstant = GodotVisualScriptConstant GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptConstant where
        type BaseClass GodotVisualScriptConstant = GodotVisualScriptNode
        super = coerce
bindVisualScriptConstant_set_constant_type
  = unsafePerformIO $
      withCString "VisualScriptConstant" $
        \ clsNamePtr ->
          withCString "set_constant_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstant_set_constant_type #-}

instance Method "set_constant_type" GodotVisualScriptConstant
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptConstant_set_constant_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptConstant_get_constant_type
  = unsafePerformIO $
      withCString "VisualScriptConstant" $
        \ clsNamePtr ->
          withCString "get_constant_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstant_get_constant_type #-}

instance Method "get_constant_type" GodotVisualScriptConstant
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptConstant_get_constant_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptConstant_set_constant_value
  = unsafePerformIO $
      withCString "VisualScriptConstant" $
        \ clsNamePtr ->
          withCString "set_constant_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstant_set_constant_value #-}

instance Method "set_constant_value" GodotVisualScriptConstant
           (GodotVariant -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptConstant_set_constant_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptConstant_get_constant_value
  = unsafePerformIO $
      withCString "VisualScriptConstant" $
        \ clsNamePtr ->
          withCString "get_constant_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstant_get_constant_value #-}

instance Method "get_constant_value" GodotVisualScriptConstant
           (IO GodotVariant)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptConstant_get_constant_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptIndexGet = GodotVisualScriptIndexGet GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptIndexGet where
        type BaseClass GodotVisualScriptIndexGet = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptIndexSet = GodotVisualScriptIndexSet GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptIndexSet where
        type BaseClass GodotVisualScriptIndexSet = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptGlobalConstant = GodotVisualScriptGlobalConstant GodotObject
                                            deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptGlobalConstant where
        type BaseClass GodotVisualScriptGlobalConstant =
             GodotVisualScriptNode
        super = coerce
bindVisualScriptGlobalConstant_set_global_constant
  = unsafePerformIO $
      withCString "VisualScriptGlobalConstant" $
        \ clsNamePtr ->
          withCString "set_global_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptGlobalConstant_set_global_constant #-}

instance Method "set_global_constant"
           GodotVisualScriptGlobalConstant
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptGlobalConstant_set_global_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptGlobalConstant_get_global_constant
  = unsafePerformIO $
      withCString "VisualScriptGlobalConstant" $
        \ clsNamePtr ->
          withCString "get_global_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptGlobalConstant_get_global_constant #-}

instance Method "get_global_constant"
           GodotVisualScriptGlobalConstant
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptGlobalConstant_get_global_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptClassConstant = GodotVisualScriptClassConstant GodotObject
                                           deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptClassConstant where
        type BaseClass GodotVisualScriptClassConstant =
             GodotVisualScriptNode
        super = coerce
bindVisualScriptClassConstant_set_class_constant
  = unsafePerformIO $
      withCString "VisualScriptClassConstant" $
        \ clsNamePtr ->
          withCString "set_class_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptClassConstant_set_class_constant #-}

instance Method "set_class_constant" GodotVisualScriptClassConstant
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptClassConstant_set_class_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptClassConstant_get_class_constant
  = unsafePerformIO $
      withCString "VisualScriptClassConstant" $
        \ clsNamePtr ->
          withCString "get_class_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptClassConstant_get_class_constant #-}

instance Method "get_class_constant" GodotVisualScriptClassConstant
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptClassConstant_get_class_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptClassConstant_set_base_type
  = unsafePerformIO $
      withCString "VisualScriptClassConstant" $
        \ clsNamePtr ->
          withCString "set_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptClassConstant_set_base_type #-}

instance Method "set_base_type" GodotVisualScriptClassConstant
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptClassConstant_set_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptClassConstant_get_base_type
  = unsafePerformIO $
      withCString "VisualScriptClassConstant" $
        \ clsNamePtr ->
          withCString "get_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptClassConstant_get_base_type #-}

instance Method "get_base_type" GodotVisualScriptClassConstant
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptClassConstant_get_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptMathConstant = GodotVisualScriptMathConstant GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptMathConstant where
        type BaseClass GodotVisualScriptMathConstant =
             GodotVisualScriptNode
        super = coerce
bindVisualScriptMathConstant_set_math_constant
  = unsafePerformIO $
      withCString "VisualScriptMathConstant" $
        \ clsNamePtr ->
          withCString "set_math_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptMathConstant_set_math_constant #-}

instance Method "set_math_constant" GodotVisualScriptMathConstant
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptMathConstant_set_math_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptMathConstant_get_math_constant
  = unsafePerformIO $
      withCString "VisualScriptMathConstant" $
        \ clsNamePtr ->
          withCString "get_math_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptMathConstant_get_math_constant #-}

instance Method "get_math_constant" GodotVisualScriptMathConstant
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptMathConstant_get_math_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptBasicTypeConstant = GodotVisualScriptBasicTypeConstant GodotObject
                                               deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptBasicTypeConstant where
        type BaseClass GodotVisualScriptBasicTypeConstant =
             GodotVisualScriptNode
        super = coerce
bindVisualScriptBasicTypeConstant_set_basic_type
  = unsafePerformIO $
      withCString "VisualScriptBasicTypeConstant" $
        \ clsNamePtr ->
          withCString "set_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptBasicTypeConstant_set_basic_type #-}

instance Method "set_basic_type" GodotVisualScriptBasicTypeConstant
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptBasicTypeConstant_set_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptBasicTypeConstant_get_basic_type
  = unsafePerformIO $
      withCString "VisualScriptBasicTypeConstant" $
        \ clsNamePtr ->
          withCString "get_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptBasicTypeConstant_get_basic_type #-}

instance Method "get_basic_type" GodotVisualScriptBasicTypeConstant
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptBasicTypeConstant_get_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptBasicTypeConstant_set_basic_type_constant
  = unsafePerformIO $
      withCString "VisualScriptBasicTypeConstant" $
        \ clsNamePtr ->
          withCString "set_basic_type_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptBasicTypeConstant_set_basic_type_constant
             #-}

instance Method "set_basic_type_constant"
           GodotVisualScriptBasicTypeConstant
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptBasicTypeConstant_set_basic_type_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptBasicTypeConstant_get_basic_type_constant
  = unsafePerformIO $
      withCString "VisualScriptBasicTypeConstant" $
        \ clsNamePtr ->
          withCString "get_basic_type_constant" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptBasicTypeConstant_get_basic_type_constant
             #-}

instance Method "get_basic_type_constant"
           GodotVisualScriptBasicTypeConstant
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptBasicTypeConstant_get_basic_type_constant
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptEngineSingleton = GodotVisualScriptEngineSingleton GodotObject
                                             deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptEngineSingleton where
        type BaseClass GodotVisualScriptEngineSingleton =
             GodotVisualScriptNode
        super = coerce
bindVisualScriptEngineSingleton_set_singleton
  = unsafePerformIO $
      withCString "VisualScriptEngineSingleton" $
        \ clsNamePtr ->
          withCString "set_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptEngineSingleton_set_singleton #-}

instance Method "set_singleton" GodotVisualScriptEngineSingleton
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptEngineSingleton_set_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptEngineSingleton_get_singleton
  = unsafePerformIO $
      withCString "VisualScriptEngineSingleton" $
        \ clsNamePtr ->
          withCString "get_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptEngineSingleton_get_singleton #-}

instance Method "get_singleton" GodotVisualScriptEngineSingleton
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptEngineSingleton_get_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptSceneNode = GodotVisualScriptSceneNode GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptSceneNode where
        type BaseClass GodotVisualScriptSceneNode = GodotVisualScriptNode
        super = coerce
bindVisualScriptSceneNode_set_node_path
  = unsafePerformIO $
      withCString "VisualScriptSceneNode" $
        \ clsNamePtr ->
          withCString "set_node_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptSceneNode_set_node_path #-}

instance Method "set_node_path" GodotVisualScriptSceneNode
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptSceneNode_set_node_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptSceneNode_get_node_path
  = unsafePerformIO $
      withCString "VisualScriptSceneNode" $
        \ clsNamePtr ->
          withCString "get_node_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptSceneNode_get_node_path #-}

instance Method "get_node_path" GodotVisualScriptSceneNode
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptSceneNode_get_node_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptSceneTree = GodotVisualScriptSceneTree GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptSceneTree where
        type BaseClass GodotVisualScriptSceneTree = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptResourcePath = GodotVisualScriptResourcePath GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptResourcePath where
        type BaseClass GodotVisualScriptResourcePath =
             GodotVisualScriptNode
        super = coerce
bindVisualScriptResourcePath_set_resource_path
  = unsafePerformIO $
      withCString "VisualScriptResourcePath" $
        \ clsNamePtr ->
          withCString "set_resource_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptResourcePath_set_resource_path #-}

instance Method "set_resource_path" GodotVisualScriptResourcePath
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptResourcePath_set_resource_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptResourcePath_get_resource_path
  = unsafePerformIO $
      withCString "VisualScriptResourcePath" $
        \ clsNamePtr ->
          withCString "get_resource_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptResourcePath_get_resource_path #-}

instance Method "get_resource_path" GodotVisualScriptResourcePath
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptResourcePath_get_resource_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptSelf = GodotVisualScriptSelf GodotObject
                                  deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptSelf where
        type BaseClass GodotVisualScriptSelf = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptCustomNode = GodotVisualScriptCustomNode GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptCustomNode where
        type BaseClass GodotVisualScriptCustomNode = GodotVisualScriptNode
        super = coerce
bindVisualScriptCustomNode__get_output_sequence_port_count
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_output_sequence_port_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_output_sequence_port_count
             #-}

instance Method "_get_output_sequence_port_count"
           GodotVisualScriptCustomNode
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_output_sequence_port_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__has_input_sequence_port
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_has_input_sequence_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__has_input_sequence_port
             #-}

instance Method "_has_input_sequence_port"
           GodotVisualScriptCustomNode
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__has_input_sequence_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_output_sequence_port_text
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_output_sequence_port_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_output_sequence_port_text
             #-}

instance Method "_get_output_sequence_port_text"
           GodotVisualScriptCustomNode
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_output_sequence_port_text
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_input_value_port_count
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_input_value_port_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_input_value_port_count
             #-}

instance Method "_get_input_value_port_count"
           GodotVisualScriptCustomNode
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_input_value_port_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_output_value_port_count
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_output_value_port_count" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_output_value_port_count
             #-}

instance Method "_get_output_value_port_count"
           GodotVisualScriptCustomNode
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_output_value_port_count
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_input_value_port_type
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_input_value_port_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_input_value_port_type
             #-}

instance Method "_get_input_value_port_type"
           GodotVisualScriptCustomNode
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_input_value_port_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_input_value_port_name
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_input_value_port_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_input_value_port_name
             #-}

instance Method "_get_input_value_port_name"
           GodotVisualScriptCustomNode
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_input_value_port_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_output_value_port_type
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_output_value_port_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_output_value_port_type
             #-}

instance Method "_get_output_value_port_type"
           GodotVisualScriptCustomNode
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_output_value_port_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_output_value_port_name
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_output_value_port_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_output_value_port_name
             #-}

instance Method "_get_output_value_port_name"
           GodotVisualScriptCustomNode
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_output_value_port_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_caption
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_caption" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_caption #-}

instance Method "_get_caption" GodotVisualScriptCustomNode
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptCustomNode__get_caption
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_text
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_text" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_text #-}

instance Method "_get_text" GodotVisualScriptCustomNode
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptCustomNode__get_text
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_category
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_category" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_category #-}

instance Method "_get_category" GodotVisualScriptCustomNode
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptCustomNode__get_category
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__get_working_memory_size
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_get_working_memory_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__get_working_memory_size
             #-}

instance Method "_get_working_memory_size"
           GodotVisualScriptCustomNode
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptCustomNode__get_working_memory_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__step
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_step" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__step #-}

instance Method "_step" GodotVisualScriptCustomNode
           (GodotArray -> GodotArray -> Int -> GodotArray -> IO GodotVariant)
         where
        runMethod cls arg1 arg2 arg3 arg4
          = withVariantArray
              [toVariant arg1, toVariant arg2, toVariant arg3, toVariant arg4]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptCustomNode__step
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptCustomNode__script_changed
  = unsafePerformIO $
      withCString "VisualScriptCustomNode" $
        \ clsNamePtr ->
          withCString "_script_changed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptCustomNode__script_changed #-}

instance Method "_script_changed" GodotVisualScriptCustomNode
           (IO ())
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptCustomNode__script_changed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptSubCall = GodotVisualScriptSubCall GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptSubCall where
        type BaseClass GodotVisualScriptSubCall = GodotVisualScriptNode
        super = coerce
bindVisualScriptSubCall__subcall
  = unsafePerformIO $
      withCString "VisualScriptSubCall" $
        \ clsNamePtr ->
          withCString "_subcall" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptSubCall__subcall #-}

instance Method "_subcall" GodotVisualScriptSubCall
           (GodotVariant -> IO GodotVariant)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptSubCall__subcall
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptComment = GodotVisualScriptComment GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptComment where
        type BaseClass GodotVisualScriptComment = GodotVisualScriptNode
        super = coerce
bindVisualScriptComment_set_title
  = unsafePerformIO $
      withCString "VisualScriptComment" $
        \ clsNamePtr ->
          withCString "set_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptComment_set_title #-}

instance Method "set_title" GodotVisualScriptComment
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptComment_set_title
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptComment_get_title
  = unsafePerformIO $
      withCString "VisualScriptComment" $
        \ clsNamePtr ->
          withCString "get_title" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptComment_get_title #-}

instance Method "get_title" GodotVisualScriptComment
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptComment_get_title
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptComment_set_description
  = unsafePerformIO $
      withCString "VisualScriptComment" $
        \ clsNamePtr ->
          withCString "set_description" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptComment_set_description #-}

instance Method "set_description" GodotVisualScriptComment
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptComment_set_description
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptComment_get_description
  = unsafePerformIO $
      withCString "VisualScriptComment" $
        \ clsNamePtr ->
          withCString "get_description" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptComment_get_description #-}

instance Method "get_description" GodotVisualScriptComment
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptComment_get_description
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptComment_set_size
  = unsafePerformIO $
      withCString "VisualScriptComment" $
        \ clsNamePtr ->
          withCString "set_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptComment_set_size #-}

instance Method "set_size" GodotVisualScriptComment
           (GodotVector2 -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptComment_set_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptComment_get_size
  = unsafePerformIO $
      withCString "VisualScriptComment" $
        \ clsNamePtr ->
          withCString "get_size" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptComment_get_size #-}

instance Method "get_size" GodotVisualScriptComment
           (IO GodotVector2)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptComment_get_size
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptConstructor = GodotVisualScriptConstructor GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptConstructor where
        type BaseClass GodotVisualScriptConstructor = GodotVisualScriptNode
        super = coerce
bindVisualScriptConstructor_set_constructor_type
  = unsafePerformIO $
      withCString "VisualScriptConstructor" $
        \ clsNamePtr ->
          withCString "set_constructor_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstructor_set_constructor_type #-}

instance Method "set_constructor_type" GodotVisualScriptConstructor
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptConstructor_set_constructor_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptConstructor_get_constructor_type
  = unsafePerformIO $
      withCString "VisualScriptConstructor" $
        \ clsNamePtr ->
          withCString "get_constructor_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstructor_get_constructor_type #-}

instance Method "get_constructor_type" GodotVisualScriptConstructor
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptConstructor_get_constructor_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptConstructor_set_constructor
  = unsafePerformIO $
      withCString "VisualScriptConstructor" $
        \ clsNamePtr ->
          withCString "set_constructor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstructor_set_constructor #-}

instance Method "set_constructor" GodotVisualScriptConstructor
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptConstructor_set_constructor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptConstructor_get_constructor
  = unsafePerformIO $
      withCString "VisualScriptConstructor" $
        \ clsNamePtr ->
          withCString "get_constructor" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptConstructor_get_constructor #-}

instance Method "get_constructor" GodotVisualScriptConstructor
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptConstructor_get_constructor
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptLocalVar = GodotVisualScriptLocalVar GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptLocalVar where
        type BaseClass GodotVisualScriptLocalVar = GodotVisualScriptNode
        super = coerce
bindVisualScriptLocalVar_set_var_name
  = unsafePerformIO $
      withCString "VisualScriptLocalVar" $
        \ clsNamePtr ->
          withCString "set_var_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVar_set_var_name #-}

instance Method "set_var_name" GodotVisualScriptLocalVar
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVar_set_var_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptLocalVar_get_var_name
  = unsafePerformIO $
      withCString "VisualScriptLocalVar" $
        \ clsNamePtr ->
          withCString "get_var_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVar_get_var_name #-}

instance Method "get_var_name" GodotVisualScriptLocalVar
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVar_get_var_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptLocalVar_set_var_type
  = unsafePerformIO $
      withCString "VisualScriptLocalVar" $
        \ clsNamePtr ->
          withCString "set_var_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVar_set_var_type #-}

instance Method "set_var_type" GodotVisualScriptLocalVar
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVar_set_var_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptLocalVar_get_var_type
  = unsafePerformIO $
      withCString "VisualScriptLocalVar" $
        \ clsNamePtr ->
          withCString "get_var_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVar_get_var_type #-}

instance Method "get_var_type" GodotVisualScriptLocalVar (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVar_get_var_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptLocalVarSet = GodotVisualScriptLocalVarSet GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptLocalVarSet where
        type BaseClass GodotVisualScriptLocalVarSet = GodotVisualScriptNode
        super = coerce
bindVisualScriptLocalVarSet_set_var_name
  = unsafePerformIO $
      withCString "VisualScriptLocalVarSet" $
        \ clsNamePtr ->
          withCString "set_var_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVarSet_set_var_name #-}

instance Method "set_var_name" GodotVisualScriptLocalVarSet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVarSet_set_var_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptLocalVarSet_get_var_name
  = unsafePerformIO $
      withCString "VisualScriptLocalVarSet" $
        \ clsNamePtr ->
          withCString "get_var_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVarSet_get_var_name #-}

instance Method "get_var_name" GodotVisualScriptLocalVarSet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVarSet_get_var_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptLocalVarSet_set_var_type
  = unsafePerformIO $
      withCString "VisualScriptLocalVarSet" $
        \ clsNamePtr ->
          withCString "set_var_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVarSet_set_var_type #-}

instance Method "set_var_type" GodotVisualScriptLocalVarSet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVarSet_set_var_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptLocalVarSet_get_var_type
  = unsafePerformIO $
      withCString "VisualScriptLocalVarSet" $
        \ clsNamePtr ->
          withCString "get_var_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptLocalVarSet_get_var_type #-}

instance Method "get_var_type" GodotVisualScriptLocalVarSet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptLocalVarSet_get_var_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptInputAction = GodotVisualScriptInputAction GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptInputAction where
        type BaseClass GodotVisualScriptInputAction = GodotVisualScriptNode
        super = coerce
bindVisualScriptInputAction_set_action_name
  = unsafePerformIO $
      withCString "VisualScriptInputAction" $
        \ clsNamePtr ->
          withCString "set_action_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptInputAction_set_action_name #-}

instance Method "set_action_name" GodotVisualScriptInputAction
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptInputAction_set_action_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptInputAction_get_action_name
  = unsafePerformIO $
      withCString "VisualScriptInputAction" $
        \ clsNamePtr ->
          withCString "get_action_name" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptInputAction_get_action_name #-}

instance Method "get_action_name" GodotVisualScriptInputAction
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptInputAction_get_action_name
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptInputAction_set_action_mode
  = unsafePerformIO $
      withCString "VisualScriptInputAction" $
        \ clsNamePtr ->
          withCString "set_action_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptInputAction_set_action_mode #-}

instance Method "set_action_mode" GodotVisualScriptInputAction
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptInputAction_set_action_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptInputAction_get_action_mode
  = unsafePerformIO $
      withCString "VisualScriptInputAction" $
        \ clsNamePtr ->
          withCString "get_action_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptInputAction_get_action_mode #-}

instance Method "get_action_mode" GodotVisualScriptInputAction
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptInputAction_get_action_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptDeconstruct = GodotVisualScriptDeconstruct GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptDeconstruct where
        type BaseClass GodotVisualScriptDeconstruct = GodotVisualScriptNode
        super = coerce
bindVisualScriptDeconstruct_set_deconstruct_type
  = unsafePerformIO $
      withCString "VisualScriptDeconstruct" $
        \ clsNamePtr ->
          withCString "set_deconstruct_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptDeconstruct_set_deconstruct_type #-}

instance Method "set_deconstruct_type" GodotVisualScriptDeconstruct
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptDeconstruct_set_deconstruct_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptDeconstruct_get_deconstruct_type
  = unsafePerformIO $
      withCString "VisualScriptDeconstruct" $
        \ clsNamePtr ->
          withCString "get_deconstruct_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptDeconstruct_get_deconstruct_type #-}

instance Method "get_deconstruct_type" GodotVisualScriptDeconstruct
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptDeconstruct_get_deconstruct_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptDeconstruct__set_elem_cache
  = unsafePerformIO $
      withCString "VisualScriptDeconstruct" $
        \ clsNamePtr ->
          withCString "_set_elem_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptDeconstruct__set_elem_cache #-}

instance Method "_set_elem_cache" GodotVisualScriptDeconstruct
           (GodotArray -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptDeconstruct__set_elem_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptDeconstruct__get_elem_cache
  = unsafePerformIO $
      withCString "VisualScriptDeconstruct" $
        \ clsNamePtr ->
          withCString "_get_elem_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptDeconstruct__get_elem_cache #-}

instance Method "_get_elem_cache" GodotVisualScriptDeconstruct
           (IO GodotArray)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptDeconstruct__get_elem_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptPreload = GodotVisualScriptPreload GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptPreload where
        type BaseClass GodotVisualScriptPreload = GodotVisualScriptNode
        super = coerce
bindVisualScriptPreload_set_preload
  = unsafePerformIO $
      withCString "VisualScriptPreload" $
        \ clsNamePtr ->
          withCString "set_preload" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPreload_set_preload #-}

instance Method "set_preload" GodotVisualScriptPreload
           (GodotResource -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPreload_set_preload
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPreload_get_preload
  = unsafePerformIO $
      withCString "VisualScriptPreload" $
        \ clsNamePtr ->
          withCString "get_preload" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPreload_get_preload #-}

instance Method "get_preload" GodotVisualScriptPreload
           (IO GodotResource)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPreload_get_preload
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptTypeCast = GodotVisualScriptTypeCast GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptTypeCast where
        type BaseClass GodotVisualScriptTypeCast = GodotVisualScriptNode
        super = coerce
bindVisualScriptTypeCast_set_base_type
  = unsafePerformIO $
      withCString "VisualScriptTypeCast" $
        \ clsNamePtr ->
          withCString "set_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptTypeCast_set_base_type #-}

instance Method "set_base_type" GodotVisualScriptTypeCast
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptTypeCast_set_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptTypeCast_get_base_type
  = unsafePerformIO $
      withCString "VisualScriptTypeCast" $
        \ clsNamePtr ->
          withCString "get_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptTypeCast_get_base_type #-}

instance Method "get_base_type" GodotVisualScriptTypeCast
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptTypeCast_get_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptTypeCast_set_base_script
  = unsafePerformIO $
      withCString "VisualScriptTypeCast" $
        \ clsNamePtr ->
          withCString "set_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptTypeCast_set_base_script #-}

instance Method "set_base_script" GodotVisualScriptTypeCast
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptTypeCast_set_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptTypeCast_get_base_script
  = unsafePerformIO $
      withCString "VisualScriptTypeCast" $
        \ clsNamePtr ->
          withCString "get_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptTypeCast_get_base_script #-}

instance Method "get_base_script" GodotVisualScriptTypeCast
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptTypeCast_get_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptFunctionCall = GodotVisualScriptFunctionCall GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptFunctionCall where
        type BaseClass GodotVisualScriptFunctionCall =
             GodotVisualScriptNode
        super = coerce
bindVisualScriptFunctionCall_set_base_type
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_base_type #-}

instance Method "set_base_type" GodotVisualScriptFunctionCall
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_base_type
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_base_type #-}

instance Method "get_base_type" GodotVisualScriptFunctionCall
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_base_script
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_base_script #-}

instance Method "set_base_script" GodotVisualScriptFunctionCall
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_base_script
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_base_script #-}

instance Method "get_base_script" GodotVisualScriptFunctionCall
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_basic_type
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_basic_type #-}

instance Method "set_basic_type" GodotVisualScriptFunctionCall
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_basic_type
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_basic_type #-}

instance Method "get_basic_type" GodotVisualScriptFunctionCall
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_singleton
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_singleton #-}

instance Method "set_singleton" GodotVisualScriptFunctionCall
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_singleton
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_singleton" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_singleton #-}

instance Method "get_singleton" GodotVisualScriptFunctionCall
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_singleton
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_function
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_function #-}

instance Method "set_function" GodotVisualScriptFunctionCall
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_function
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_function" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_function #-}

instance Method "get_function" GodotVisualScriptFunctionCall
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_function
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_call_mode
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_call_mode #-}

instance Method "set_call_mode" GodotVisualScriptFunctionCall
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_call_mode
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_call_mode #-}

instance Method "get_call_mode" GodotVisualScriptFunctionCall
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_base_path
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_base_path #-}

instance Method "set_base_path" GodotVisualScriptFunctionCall
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_base_path
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_base_path #-}

instance Method "get_base_path" GodotVisualScriptFunctionCall
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_use_default_args
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_use_default_args" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_use_default_args #-}

instance Method "set_use_default_args"
           GodotVisualScriptFunctionCall
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptFunctionCall_set_use_default_args
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_use_default_args
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_use_default_args" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_use_default_args #-}

instance Method "get_use_default_args"
           GodotVisualScriptFunctionCall
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptFunctionCall_get_use_default_args
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall__set_argument_cache
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "_set_argument_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall__set_argument_cache #-}

instance Method "_set_argument_cache" GodotVisualScriptFunctionCall
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptFunctionCall__set_argument_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall__get_argument_cache
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "_get_argument_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall__get_argument_cache #-}

instance Method "_get_argument_cache" GodotVisualScriptFunctionCall
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptFunctionCall__get_argument_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_rpc_call_mode
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_rpc_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_rpc_call_mode #-}

instance Method "set_rpc_call_mode" GodotVisualScriptFunctionCall
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptFunctionCall_set_rpc_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_rpc_call_mode
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_rpc_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_rpc_call_mode #-}

instance Method "get_rpc_call_mode" GodotVisualScriptFunctionCall
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptFunctionCall_get_rpc_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_set_validate
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "set_validate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_set_validate #-}

instance Method "set_validate" GodotVisualScriptFunctionCall
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_set_validate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptFunctionCall_get_validate
  = unsafePerformIO $
      withCString "VisualScriptFunctionCall" $
        \ clsNamePtr ->
          withCString "get_validate" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptFunctionCall_get_validate #-}

instance Method "get_validate" GodotVisualScriptFunctionCall
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptFunctionCall_get_validate
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptPropertySet = GodotVisualScriptPropertySet GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptPropertySet where
        type BaseClass GodotVisualScriptPropertySet = GodotVisualScriptNode
        super = coerce
bindVisualScriptPropertySet_set_base_type
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_base_type #-}

instance Method "set_base_type" GodotVisualScriptPropertySet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_base_type
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_base_type #-}

instance Method "get_base_type" GodotVisualScriptPropertySet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_set_base_script
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_base_script #-}

instance Method "set_base_script" GodotVisualScriptPropertySet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_base_script
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_base_script #-}

instance Method "get_base_script" GodotVisualScriptPropertySet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_set_basic_type
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_basic_type #-}

instance Method "set_basic_type" GodotVisualScriptPropertySet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_basic_type
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_basic_type #-}

instance Method "get_basic_type" GodotVisualScriptPropertySet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet__set_type_cache
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "_set_type_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet__set_type_cache #-}

instance Method "_set_type_cache" GodotVisualScriptPropertySet
           (GodotDictionary -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet__set_type_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet__get_type_cache
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "_get_type_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet__get_type_cache #-}

instance Method "_get_type_cache" GodotVisualScriptPropertySet
           (IO GodotDictionary)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet__get_type_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_set_property
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_property #-}

instance Method "set_property" GodotVisualScriptPropertySet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_property
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_property
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_property #-}

instance Method "get_property" GodotVisualScriptPropertySet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_property
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_set_call_mode
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_call_mode #-}

instance Method "set_call_mode" GodotVisualScriptPropertySet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_call_mode
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_call_mode #-}

instance Method "get_call_mode" GodotVisualScriptPropertySet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_set_base_path
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_base_path #-}

instance Method "set_base_path" GodotVisualScriptPropertySet
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_base_path
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_base_path #-}

instance Method "get_base_path" GodotVisualScriptPropertySet
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_set_index
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_index #-}

instance Method "set_index" GodotVisualScriptPropertySet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_index
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_index #-}

instance Method "get_index" GodotVisualScriptPropertySet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_set_assign_op
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "set_assign_op" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_set_assign_op #-}

instance Method "set_assign_op" GodotVisualScriptPropertySet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_set_assign_op
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertySet_get_assign_op
  = unsafePerformIO $
      withCString "VisualScriptPropertySet" $
        \ clsNamePtr ->
          withCString "get_assign_op" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertySet_get_assign_op #-}

instance Method "get_assign_op" GodotVisualScriptPropertySet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertySet_get_assign_op
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptPropertyGet = GodotVisualScriptPropertyGet GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptPropertyGet where
        type BaseClass GodotVisualScriptPropertyGet = GodotVisualScriptNode
        super = coerce
bindVisualScriptPropertyGet_set_base_type
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "set_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_set_base_type #-}

instance Method "set_base_type" GodotVisualScriptPropertyGet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_set_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_get_base_type
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "get_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_get_base_type #-}

instance Method "get_base_type" GodotVisualScriptPropertyGet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_get_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_set_base_script
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "set_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_set_base_script #-}

instance Method "set_base_script" GodotVisualScriptPropertyGet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_set_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_get_base_script
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "get_base_script" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_get_base_script #-}

instance Method "get_base_script" GodotVisualScriptPropertyGet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_get_base_script
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_set_basic_type
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "set_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_set_basic_type #-}

instance Method "set_basic_type" GodotVisualScriptPropertyGet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_set_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_get_basic_type
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "get_basic_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_get_basic_type #-}

instance Method "get_basic_type" GodotVisualScriptPropertyGet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_get_basic_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet__set_type_cache
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "_set_type_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet__set_type_cache #-}

instance Method "_set_type_cache" GodotVisualScriptPropertyGet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet__set_type_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet__get_type_cache
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "_get_type_cache" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet__get_type_cache #-}

instance Method "_get_type_cache" GodotVisualScriptPropertyGet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet__get_type_cache
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_set_property
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "set_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_set_property #-}

instance Method "set_property" GodotVisualScriptPropertyGet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_set_property
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_get_property
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "get_property" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_get_property #-}

instance Method "get_property" GodotVisualScriptPropertyGet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_get_property
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_set_call_mode
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "set_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_set_call_mode #-}

instance Method "set_call_mode" GodotVisualScriptPropertyGet
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_set_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_get_call_mode
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "get_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_get_call_mode #-}

instance Method "get_call_mode" GodotVisualScriptPropertyGet
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_get_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_set_base_path
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "set_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_set_base_path #-}

instance Method "set_base_path" GodotVisualScriptPropertyGet
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_set_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_get_base_path
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "get_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_get_base_path #-}

instance Method "get_base_path" GodotVisualScriptPropertyGet
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_get_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_set_index
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "set_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_set_index #-}

instance Method "set_index" GodotVisualScriptPropertyGet
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_set_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptPropertyGet_get_index
  = unsafePerformIO $
      withCString "VisualScriptPropertyGet" $
        \ clsNamePtr ->
          withCString "get_index" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptPropertyGet_get_index #-}

instance Method "get_index" GodotVisualScriptPropertyGet
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptPropertyGet_get_index
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptEmitSignal = GodotVisualScriptEmitSignal GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptEmitSignal where
        type BaseClass GodotVisualScriptEmitSignal = GodotVisualScriptNode
        super = coerce
bindVisualScriptEmitSignal_set_signal
  = unsafePerformIO $
      withCString "VisualScriptEmitSignal" $
        \ clsNamePtr ->
          withCString "set_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptEmitSignal_set_signal #-}

instance Method "set_signal" GodotVisualScriptEmitSignal
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptEmitSignal_set_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptEmitSignal_get_signal
  = unsafePerformIO $
      withCString "VisualScriptEmitSignal" $
        \ clsNamePtr ->
          withCString "get_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptEmitSignal_get_signal #-}

instance Method "get_signal" GodotVisualScriptEmitSignal
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptEmitSignal_get_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptReturn = GodotVisualScriptReturn GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptReturn where
        type BaseClass GodotVisualScriptReturn = GodotVisualScriptNode
        super = coerce
bindVisualScriptReturn_set_return_type
  = unsafePerformIO $
      withCString "VisualScriptReturn" $
        \ clsNamePtr ->
          withCString "set_return_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptReturn_set_return_type #-}

instance Method "set_return_type" GodotVisualScriptReturn
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptReturn_set_return_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptReturn_get_return_type
  = unsafePerformIO $
      withCString "VisualScriptReturn" $
        \ clsNamePtr ->
          withCString "get_return_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptReturn_get_return_type #-}

instance Method "get_return_type" GodotVisualScriptReturn (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptReturn_get_return_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptReturn_set_enable_return_value
  = unsafePerformIO $
      withCString "VisualScriptReturn" $
        \ clsNamePtr ->
          withCString "set_enable_return_value" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptReturn_set_enable_return_value #-}

instance Method "set_enable_return_value" GodotVisualScriptReturn
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptReturn_set_enable_return_value
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptReturn_is_return_value_enabled
  = unsafePerformIO $
      withCString "VisualScriptReturn" $
        \ clsNamePtr ->
          withCString "is_return_value_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptReturn_is_return_value_enabled #-}

instance Method "is_return_value_enabled" GodotVisualScriptReturn
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call
                   bindVisualScriptReturn_is_return_value_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptCondition = GodotVisualScriptCondition GodotObject
                                       deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptCondition where
        type BaseClass GodotVisualScriptCondition = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptWhile = GodotVisualScriptWhile GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptWhile where
        type BaseClass GodotVisualScriptWhile = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptIterator = GodotVisualScriptIterator GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptIterator where
        type BaseClass GodotVisualScriptIterator = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptSequence = GodotVisualScriptSequence GodotObject
                                      deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptSequence where
        type BaseClass GodotVisualScriptSequence = GodotVisualScriptNode
        super = coerce
bindVisualScriptSequence_set_steps
  = unsafePerformIO $
      withCString "VisualScriptSequence" $
        \ clsNamePtr ->
          withCString "set_steps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptSequence_set_steps #-}

instance Method "set_steps" GodotVisualScriptSequence
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptSequence_set_steps
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptSequence_get_steps
  = unsafePerformIO $
      withCString "VisualScriptSequence" $
        \ clsNamePtr ->
          withCString "get_steps" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptSequence_get_steps #-}

instance Method "get_steps" GodotVisualScriptSequence (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptSequence_get_steps
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptSwitch = GodotVisualScriptSwitch GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptSwitch where
        type BaseClass GodotVisualScriptSwitch = GodotVisualScriptNode
        super = coerce

newtype GodotVisualScriptSelect = GodotVisualScriptSelect GodotObject
                                    deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptSelect where
        type BaseClass GodotVisualScriptSelect = GodotVisualScriptNode
        super = coerce
bindVisualScriptSelect_set_typed
  = unsafePerformIO $
      withCString "VisualScriptSelect" $
        \ clsNamePtr ->
          withCString "set_typed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptSelect_set_typed #-}

instance Method "set_typed" GodotVisualScriptSelect (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptSelect_set_typed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptSelect_get_typed
  = unsafePerformIO $
      withCString "VisualScriptSelect" $
        \ clsNamePtr ->
          withCString "get_typed" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptSelect_get_typed #-}

instance Method "get_typed" GodotVisualScriptSelect (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptSelect_get_typed
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptYield = GodotVisualScriptYield GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptYield where
        type BaseClass GodotVisualScriptYield = GodotVisualScriptNode
        super = coerce
bindVisualScriptYield_set_yield_mode
  = unsafePerformIO $
      withCString "VisualScriptYield" $
        \ clsNamePtr ->
          withCString "set_yield_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYield_set_yield_mode #-}

instance Method "set_yield_mode" GodotVisualScriptYield
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYield_set_yield_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYield_get_yield_mode
  = unsafePerformIO $
      withCString "VisualScriptYield" $
        \ clsNamePtr ->
          withCString "get_yield_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYield_get_yield_mode #-}

instance Method "get_yield_mode" GodotVisualScriptYield (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYield_get_yield_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYield_set_wait_time
  = unsafePerformIO $
      withCString "VisualScriptYield" $
        \ clsNamePtr ->
          withCString "set_wait_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYield_set_wait_time #-}

instance Method "set_wait_time" GodotVisualScriptYield
           (Float -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYield_set_wait_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYield_get_wait_time
  = unsafePerformIO $
      withCString "VisualScriptYield" $
        \ clsNamePtr ->
          withCString "get_wait_time" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYield_get_wait_time #-}

instance Method "get_wait_time" GodotVisualScriptYield (IO Float)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYield_get_wait_time
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptYieldSignal = GodotVisualScriptYieldSignal GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptYieldSignal where
        type BaseClass GodotVisualScriptYieldSignal = GodotVisualScriptNode
        super = coerce
bindVisualScriptYieldSignal_set_base_type
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "set_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_set_base_type #-}

instance Method "set_base_type" GodotVisualScriptYieldSignal
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_set_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYieldSignal_get_base_type
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "get_base_type" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_get_base_type #-}

instance Method "get_base_type" GodotVisualScriptYieldSignal
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_get_base_type
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYieldSignal_set_signal
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "set_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_set_signal #-}

instance Method "set_signal" GodotVisualScriptYieldSignal
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_set_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYieldSignal_get_signal
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "get_signal" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_get_signal #-}

instance Method "get_signal" GodotVisualScriptYieldSignal
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_get_signal
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYieldSignal_set_call_mode
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "set_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_set_call_mode #-}

instance Method "set_call_mode" GodotVisualScriptYieldSignal
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_set_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYieldSignal_get_call_mode
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "get_call_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_get_call_mode #-}

instance Method "get_call_mode" GodotVisualScriptYieldSignal
           (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_get_call_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYieldSignal_set_base_path
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "set_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_set_base_path #-}

instance Method "set_base_path" GodotVisualScriptYieldSignal
           (GodotNodePath -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_set_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptYieldSignal_get_base_path
  = unsafePerformIO $
      withCString "VisualScriptYieldSignal" $
        \ clsNamePtr ->
          withCString "get_base_path" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptYieldSignal_get_base_path #-}

instance Method "get_base_path" GodotVisualScriptYieldSignal
           (IO GodotNodePath)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptYieldSignal_get_base_path
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptBuiltinFunc = GodotVisualScriptBuiltinFunc GodotObject
                                         deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptBuiltinFunc where
        type BaseClass GodotVisualScriptBuiltinFunc = GodotVisualScriptNode
        super = coerce
bindVisualScriptBuiltinFunc_set_func
  = unsafePerformIO $
      withCString "VisualScriptBuiltinFunc" $
        \ clsNamePtr ->
          withCString "set_func" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptBuiltinFunc_set_func #-}

instance Method "set_func" GodotVisualScriptBuiltinFunc
           (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptBuiltinFunc_set_func
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVisualScriptBuiltinFunc_get_func
  = unsafePerformIO $
      withCString "VisualScriptBuiltinFunc" $
        \ clsNamePtr ->
          withCString "get_func" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVisualScriptBuiltinFunc_get_func #-}

instance Method "get_func" GodotVisualScriptBuiltinFunc (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVisualScriptBuiltinFunc_get_func
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotVisualScriptExpression = GodotVisualScriptExpression GodotObject
                                        deriving newtype AsVariant

instance HasBaseClass GodotVisualScriptExpression where
        type BaseClass GodotVisualScriptExpression = GodotVisualScriptNode
        super = coerce

newtype GodotVideoStreamWebm = GodotVideoStreamWebm GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotVideoStreamWebm where
        type BaseClass GodotVideoStreamWebm = GodotVideoStream
        super = coerce
bindVideoStreamWebm_set_file
  = unsafePerformIO $
      withCString "VideoStreamWebm" $
        \ clsNamePtr ->
          withCString "set_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoStreamWebm_set_file #-}

instance Method "set_file" GodotVideoStreamWebm
           (GodotString -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoStreamWebm_set_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindVideoStreamWebm_get_file
  = unsafePerformIO $
      withCString "VideoStreamWebm" $
        \ clsNamePtr ->
          withCString "get_file" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindVideoStreamWebm_get_file #-}

instance Method "get_file" GodotVideoStreamWebm (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindVideoStreamWebm_get_file (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype Godot_VisualScriptEditor = Godot_VisualScriptEditor GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass Godot_VisualScriptEditor where
        type BaseClass Godot_VisualScriptEditor = GodotObject
        super = coerce
bind_VisualScriptEditor_add_custom_node
  = unsafePerformIO $
      withCString "_VisualScriptEditor" $
        \ clsNamePtr ->
          withCString "add_custom_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_VisualScriptEditor_add_custom_node #-}

instance Method "add_custom_node" Godot_VisualScriptEditor
           (GodotString -> GodotString -> GodotScript -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_VisualScriptEditor_add_custom_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bind_VisualScriptEditor_remove_custom_node
  = unsafePerformIO $
      withCString "_VisualScriptEditor" $
        \ clsNamePtr ->
          withCString "remove_custom_node" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bind_VisualScriptEditor_remove_custom_node #-}

instance Method "remove_custom_node" Godot_VisualScriptEditor
           (GodotString -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bind_VisualScriptEditor_remove_custom_node
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWebSocketServer = GodotWebSocketServer GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotWebSocketServer where
        type BaseClass GodotWebSocketServer = GodotWebSocketMultiplayerPeer
        super = coerce
bindWebSocketServer_is_listening
  = unsafePerformIO $
      withCString "WebSocketServer" $
        \ clsNamePtr ->
          withCString "is_listening" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketServer_is_listening #-}

instance Method "is_listening" GodotWebSocketServer (IO Bool) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketServer_is_listening
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketServer_listen
  = unsafePerformIO $
      withCString "WebSocketServer" $
        \ clsNamePtr ->
          withCString "listen" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketServer_listen #-}

instance Method "listen" GodotWebSocketServer
           (Int -> GodotPoolStringArray -> Bool -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketServer_listen (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketServer_stop
  = unsafePerformIO $
      withCString "WebSocketServer" $
        \ clsNamePtr ->
          withCString "stop" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketServer_stop #-}

instance Method "stop" GodotWebSocketServer (IO ()) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketServer_stop (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketServer_has_peer
  = unsafePerformIO $
      withCString "WebSocketServer" $
        \ clsNamePtr ->
          withCString "has_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketServer_has_peer #-}

instance Method "has_peer" GodotWebSocketServer (Int -> IO Bool)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketServer_has_peer (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketServer_get_peer_address
  = unsafePerformIO $
      withCString "WebSocketServer" $
        \ clsNamePtr ->
          withCString "get_peer_address" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketServer_get_peer_address #-}

instance Method "get_peer_address" GodotWebSocketServer
           (Int -> IO GodotString)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketServer_get_peer_address
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketServer_get_peer_port
  = unsafePerformIO $
      withCString "WebSocketServer" $
        \ clsNamePtr ->
          withCString "get_peer_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketServer_get_peer_port #-}

instance Method "get_peer_port" GodotWebSocketServer
           (Int -> IO Int)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketServer_get_peer_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketServer_disconnect_peer
  = unsafePerformIO $
      withCString "WebSocketServer" $
        \ clsNamePtr ->
          withCString "disconnect_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketServer_disconnect_peer #-}

instance Method "disconnect_peer" GodotWebSocketServer
           (Int -> Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketServer_disconnect_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWebSocketMultiplayerPeer = GodotWebSocketMultiplayerPeer GodotObject
                                          deriving newtype AsVariant

instance HasBaseClass GodotWebSocketMultiplayerPeer where
        type BaseClass GodotWebSocketMultiplayerPeer =
             GodotNetworkedMultiplayerPeer
        super = coerce
bindWebSocketMultiplayerPeer_get_peer
  = unsafePerformIO $
      withCString "WebSocketMultiplayerPeer" $
        \ clsNamePtr ->
          withCString "get_peer" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketMultiplayerPeer_get_peer #-}

instance Method "get_peer" GodotWebSocketMultiplayerPeer
           (Int -> IO GodotWebSocketPeer)
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketMultiplayerPeer_get_peer
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWebSocketClient = GodotWebSocketClient GodotObject
                                 deriving newtype AsVariant

instance HasBaseClass GodotWebSocketClient where
        type BaseClass GodotWebSocketClient = GodotWebSocketMultiplayerPeer
        super = coerce
bindWebSocketClient_connect_to_url
  = unsafePerformIO $
      withCString "WebSocketClient" $
        \ clsNamePtr ->
          withCString "connect_to_url" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketClient_connect_to_url #-}

instance Method "connect_to_url" GodotWebSocketClient
           (GodotString -> GodotPoolStringArray -> Bool -> IO Int)
         where
        runMethod cls arg1 arg2 arg3
          = withVariantArray [toVariant arg1, toVariant arg2, toVariant arg3]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketClient_connect_to_url
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketClient_disconnect_from_host
  = unsafePerformIO $
      withCString "WebSocketClient" $
        \ clsNamePtr ->
          withCString "disconnect_from_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketClient_disconnect_from_host #-}

instance Method "disconnect_from_host" GodotWebSocketClient
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketClient_disconnect_from_host
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketClient_set_verify_ssl_enabled
  = unsafePerformIO $
      withCString "WebSocketClient" $
        \ clsNamePtr ->
          withCString "set_verify_ssl_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketClient_set_verify_ssl_enabled #-}

instance Method "set_verify_ssl_enabled" GodotWebSocketClient
           (Bool -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketClient_set_verify_ssl_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketClient_is_verify_ssl_enabled
  = unsafePerformIO $
      withCString "WebSocketClient" $
        \ clsNamePtr ->
          withCString "is_verify_ssl_enabled" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketClient_is_verify_ssl_enabled #-}

instance Method "is_verify_ssl_enabled" GodotWebSocketClient
           (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketClient_is_verify_ssl_enabled
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotWebSocketPeer = GodotWebSocketPeer GodotObject
                               deriving newtype AsVariant

instance HasBaseClass GodotWebSocketPeer where
        type BaseClass GodotWebSocketPeer = GodotPacketPeer
        super = coerce
bindWebSocketPeer_get_write_mode
  = unsafePerformIO $
      withCString "WebSocketPeer" $
        \ clsNamePtr ->
          withCString "get_write_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketPeer_get_write_mode #-}

instance Method "get_write_mode" GodotWebSocketPeer (IO Int) where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketPeer_get_write_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketPeer_set_write_mode
  = unsafePerformIO $
      withCString "WebSocketPeer" $
        \ clsNamePtr ->
          withCString "set_write_mode" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketPeer_set_write_mode #-}

instance Method "set_write_mode" GodotWebSocketPeer (Int -> IO ())
         where
        runMethod cls arg1
          = withVariantArray [toVariant arg1]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketPeer_set_write_mode
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketPeer_is_connected_to_host
  = unsafePerformIO $
      withCString "WebSocketPeer" $
        \ clsNamePtr ->
          withCString "is_connected_to_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketPeer_is_connected_to_host #-}

instance Method "is_connected_to_host" GodotWebSocketPeer (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketPeer_is_connected_to_host
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketPeer_was_string_packet
  = unsafePerformIO $
      withCString "WebSocketPeer" $
        \ clsNamePtr ->
          withCString "was_string_packet" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketPeer_was_string_packet #-}

instance Method "was_string_packet" GodotWebSocketPeer (IO Bool)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketPeer_was_string_packet
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketPeer_close
  = unsafePerformIO $
      withCString "WebSocketPeer" $
        \ clsNamePtr ->
          withCString "close" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketPeer_close #-}

instance Method "close" GodotWebSocketPeer
           (Int -> GodotString -> IO ())
         where
        runMethod cls arg1 arg2
          = withVariantArray [toVariant arg1, toVariant arg2]
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketPeer_close (coerce cls) arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketPeer_get_connected_host
  = unsafePerformIO $
      withCString "WebSocketPeer" $
        \ clsNamePtr ->
          withCString "get_connected_host" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketPeer_get_connected_host #-}

instance Method "get_connected_host" GodotWebSocketPeer
           (IO GodotString)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketPeer_get_connected_host
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)
bindWebSocketPeer_get_connected_port
  = unsafePerformIO $
      withCString "WebSocketPeer" $
        \ clsNamePtr ->
          withCString "get_connected_port" $
            \ methodNamePtr ->
              godot_method_bind_get_method clsNamePtr methodNamePtr

{-# NOINLINE bindWebSocketPeer_get_connected_port #-}

instance Method "get_connected_port" GodotWebSocketPeer (IO Int)
         where
        runMethod cls
          = withVariantArray []
              (\ (arrPtr, len) ->
                 godot_method_bind_call bindWebSocketPeer_get_connected_port
                   (coerce cls)
                   arrPtr
                   len
                   >>= \ (err, res) -> throwIfErr err >> fromGodotVariant res)

newtype GodotBulletPhysicsServer = GodotBulletPhysicsServer GodotObject
                                     deriving newtype AsVariant

instance HasBaseClass GodotBulletPhysicsServer where
        type BaseClass GodotBulletPhysicsServer = GodotPhysicsServer
        super = coerce

newtype GodotBulletPhysicsDirectBodyState = GodotBulletPhysicsDirectBodyState GodotObject
                                              deriving newtype AsVariant

instance HasBaseClass GodotBulletPhysicsDirectBodyState where
        type BaseClass GodotBulletPhysicsDirectBodyState =
             GodotPhysicsDirectBodyState
        super = coerce

newtype GodotPhysics2DServerSW = GodotPhysics2DServerSW GodotObject
                                   deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DServerSW where
        type BaseClass GodotPhysics2DServerSW = GodotPhysics2DServer
        super = coerce

newtype GodotPhysics2DDirectBodyStateSW = GodotPhysics2DDirectBodyStateSW GodotObject
                                            deriving newtype AsVariant

instance HasBaseClass GodotPhysics2DDirectBodyStateSW where
        type BaseClass GodotPhysics2DDirectBodyStateSW =
             GodotPhysics2DDirectBodyState
        super = coerce