Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
data GodotVariantType Source #
Instances
data GodotVariantCallErrorError Source #
Instances
data GodotError Source #
Instances
data GodotVector3Axis Source #
Instances
data GodotVariantOperator Source #
Instances
type GodotCharType = CInt Source #
Instances
newtype GodotArray Source #
Instances
withGodotArray :: GodotArray -> (Ptr GodotArray -> IO b) -> IO b Source #
newtype GodotBasis Source #
Instances
withGodotBasis :: GodotBasis -> (Ptr GodotBasis -> IO b) -> IO b Source #
newtype GodotCharString Source #
Instances
Eq GodotCharString Source # | |
Defined in Godot.Gdnative.Internal.Gdnative (==) :: GodotCharString -> GodotCharString -> Bool # (/=) :: GodotCharString -> GodotCharString -> Bool # | |
OpaqueStorable GodotCharString Source # | |
Defined in Godot.Gdnative.Internal.Gdnative opaqueSizeOf :: Int Source # |
withGodotCharString :: GodotCharString -> (Ptr GodotCharString -> IO b) -> IO b Source #
newtype GodotColor Source #
Instances
withGodotColor :: GodotColor -> (Ptr GodotColor -> IO b) -> IO b Source #
newtype GodotDictionary Source #
Instances
withGodotDictionary :: GodotDictionary -> (Ptr GodotDictionary -> IO b) -> IO b Source #
newtype GodotMethodBind Source #
Instances
Eq GodotMethodBind Source # | |
Defined in Godot.Gdnative.Internal.Gdnative (==) :: GodotMethodBind -> GodotMethodBind -> Bool # (/=) :: GodotMethodBind -> GodotMethodBind -> Bool # | |
OpaqueStorable GodotMethodBind Source # | |
Defined in Godot.Gdnative.Internal.Gdnative opaqueSizeOf :: Int Source # |
withGodotMethodBind :: GodotMethodBind -> (Ptr GodotMethodBind -> IO b) -> IO b Source #
newtype GodotNodePath Source #
Instances
withGodotNodePath :: GodotNodePath -> (Ptr GodotNodePath -> IO b) -> IO b Source #
newtype GodotPlane Source #
Instances
withGodotPlane :: GodotPlane -> (Ptr GodotPlane -> IO b) -> IO b Source #
newtype GodotPoolArrayReadAccess Source #
Instances
withGodotPoolArrayReadAccess :: GodotPoolArrayReadAccess -> (Ptr GodotPoolArrayReadAccess -> IO b) -> IO b Source #
newtype GodotPoolArrayWriteAccess Source #
Instances
withGodotPoolArrayWriteAccess :: GodotPoolArrayWriteAccess -> (Ptr GodotPoolArrayWriteAccess -> IO b) -> IO b Source #
newtype GodotPoolByteArray Source #
Instances
withGodotPoolByteArray :: GodotPoolByteArray -> (Ptr GodotPoolByteArray -> IO b) -> IO b Source #
newtype GodotPoolColorArray Source #
Instances
withGodotPoolColorArray :: GodotPoolColorArray -> (Ptr GodotPoolColorArray -> IO b) -> IO b Source #
newtype GodotPoolIntArray Source #
Instances
withGodotPoolIntArray :: GodotPoolIntArray -> (Ptr GodotPoolIntArray -> IO b) -> IO b Source #
newtype GodotPoolRealArray Source #
Instances
withGodotPoolRealArray :: GodotPoolRealArray -> (Ptr GodotPoolRealArray -> IO b) -> IO b Source #
newtype GodotPoolStringArray Source #
Instances
withGodotPoolStringArray :: GodotPoolStringArray -> (Ptr GodotPoolStringArray -> IO b) -> IO b Source #
newtype GodotPoolVector2Array Source #
Instances
withGodotPoolVector2Array :: GodotPoolVector2Array -> (Ptr GodotPoolVector2Array -> IO b) -> IO b Source #
newtype GodotPoolVector3Array Source #
Instances
withGodotPoolVector3Array :: GodotPoolVector3Array -> (Ptr GodotPoolVector3Array -> IO b) -> IO b Source #
Instances
Eq GodotQuat Source # | |
AsVariant GodotQuat Source # | |
Method "transform_track_insert_key" GodotAnimation (Int -> Float -> GodotVector3 -> GodotQuat -> GodotVector3 -> IO Int) Source # | |
Defined in Godot.Api.Auto runMethod :: GodotAnimation -> Int -> Float -> GodotVector3 -> GodotQuat -> GodotVector3 -> IO Int Source # | |
GodotFFI GodotQuat (Quaternion Float) Source # | |
Defined in Godot.Gdnative.Types fromLowLevel :: GodotQuat -> IO (Quaternion Float) Source # toLowLevel :: Quaternion Float -> IO GodotQuat Source # | |
OpaqueStorable GodotQuat Source # | |
Defined in Godot.Gdnative.Internal.Gdnative opaqueSizeOf :: Int Source # | |
type TypeOf HaskellTy GodotQuat Source # | |
Defined in Godot.Gdnative.Types |
newtype GodotRect2 Source #
Instances
withGodotRect2 :: GodotRect2 -> (Ptr GodotRect2 -> IO b) -> IO b Source #
Instances
newtype GodotString Source #
Instances
withGodotString :: GodotString -> (Ptr GodotString -> IO b) -> IO b Source #
newtype GodotStringName Source #
Instances
Eq GodotStringName Source # | |
Defined in Godot.Gdnative.Internal.Gdnative (==) :: GodotStringName -> GodotStringName -> Bool # (/=) :: GodotStringName -> GodotStringName -> Bool # | |
OpaqueStorable GodotStringName Source # | |
Defined in Godot.Gdnative.Internal.Gdnative opaqueSizeOf :: Int Source # |
withGodotStringName :: GodotStringName -> (Ptr GodotStringName -> IO b) -> IO b Source #
newtype GodotTransform Source #
Instances
withGodotTransform :: GodotTransform -> (Ptr GodotTransform -> IO b) -> IO b Source #
newtype GodotTransform2d Source #
Instances
withGodotTransform2d :: GodotTransform2d -> (Ptr GodotTransform2d -> IO b) -> IO b Source #
newtype GodotVariant Source #
Instances
withGodotVariant :: GodotVariant -> (Ptr GodotVariant -> IO b) -> IO b Source #
newtype GodotVector2 Source #
Instances
withGodotVector2 :: GodotVector2 -> (Ptr GodotVector2 -> IO b) -> IO b Source #
newtype GodotVector3 Source #
Instances
withGodotVector3 :: GodotVector3 -> (Ptr GodotVector3 -> IO b) -> IO b Source #
class OpaqueStorable a where Source #
opaqueSizeOf :: Int Source #
Instances
data GodotVariantCallError Source #
Instances
newtype GodotGdnativeApiStruct Source #
Instances
Eq GodotGdnativeApiStruct Source # | |
Defined in Godot.Gdnative.Internal.Gdnative | |
Storable GodotGdnativeApiStruct Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotGdnativeApiStruct -> Int # alignment :: GodotGdnativeApiStruct -> Int # peekElemOff :: Ptr GodotGdnativeApiStruct -> Int -> IO GodotGdnativeApiStruct # pokeElemOff :: Ptr GodotGdnativeApiStruct -> Int -> GodotGdnativeApiStruct -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotGdnativeApiStruct # pokeByteOff :: Ptr b -> Int -> GodotGdnativeApiStruct -> IO () # peek :: Ptr GodotGdnativeApiStruct -> IO GodotGdnativeApiStruct # poke :: Ptr GodotGdnativeApiStruct -> GodotGdnativeApiStruct -> IO () # |
newtype GodotGdnativeCoreApiStruct Source #
Instances
Eq GodotGdnativeCoreApiStruct Source # | |
Storable GodotGdnativeCoreApiStruct Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotGdnativeCoreApiStruct -> Int # alignment :: GodotGdnativeCoreApiStruct -> Int # peekElemOff :: Ptr GodotGdnativeCoreApiStruct -> Int -> IO GodotGdnativeCoreApiStruct # pokeElemOff :: Ptr GodotGdnativeCoreApiStruct -> Int -> GodotGdnativeCoreApiStruct -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotGdnativeCoreApiStruct # pokeByteOff :: Ptr b -> Int -> GodotGdnativeCoreApiStruct -> IO () # peek :: Ptr GodotGdnativeCoreApiStruct -> IO GodotGdnativeCoreApiStruct # poke :: Ptr GodotGdnativeCoreApiStruct -> GodotGdnativeCoreApiStruct -> IO () # |
newtype GodotGdnativeCore11ApiStruct Source #
Instances
newtype GodotGdnativeExtNativescriptApiStruct Source #
Instances
newtype GodotGdnativeExtNativescript11ApiStruct Source #
Instances
newtype GodotGdnativeExtPluginscriptApiStruct Source #
Instances
newtype GodotGdnativeExtArvrApiStruct Source #
Instances
type ReportVersionMismatchFunc = GodotObject -> CString -> Word64 -> Word64 -> IO () Source #
type ReportLoadingErrorFunc = GodotObject -> CString -> IO () Source #
newtype GodotObject Source #
Instances
data GodotGdnativeInitOptions Source #
Instances
Storable GodotGdnativeInitOptions Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotGdnativeInitOptions -> Int # alignment :: GodotGdnativeInitOptions -> Int # peekElemOff :: Ptr GodotGdnativeInitOptions -> Int -> IO GodotGdnativeInitOptions # pokeElemOff :: Ptr GodotGdnativeInitOptions -> Int -> GodotGdnativeInitOptions -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotGdnativeInitOptions # pokeByteOff :: Ptr b -> Int -> GodotGdnativeInitOptions -> IO () # peek :: Ptr GodotGdnativeInitOptions -> IO GodotGdnativeInitOptions # poke :: Ptr GodotGdnativeInitOptions -> GodotGdnativeInitOptions -> IO () # |
mkReportVersionMismatchFunc :: FunPtr ReportVersionMismatchFunc -> ReportVersionMismatchFunc Source #
data GodotGdnativeTerminateOptions Source #
Instances
type NativeCallCb = FunPtr (Ptr GodotVariant -> Ptr () -> GodotArray -> IO (Ptr GodotVariant)) Source #
type GodotClassConstructor = FunPtr (IO GodotObject) Source #
data GodotPluginscriptLanguageDesc Source #
Instances
data GodotPropertyHint Source #
Instances
data GodotMethodRpcMode Source #
Instances
newtype GodotPropertyUsageFlags Source #
Instances
pattern GodotPropertyUsageStorage :: GodotPropertyUsageFlags Source #
pattern GodotPropertyUsageEditor :: GodotPropertyUsageFlags Source #
pattern GodotPropertyUsageNetwork :: GodotPropertyUsageFlags Source #
pattern GodotPropertyUsageChecked :: GodotPropertyUsageFlags Source #
pattern GodotPropertyUsageGroup :: GodotPropertyUsageFlags Source #
pattern GodotPropertyUsageCategory :: GodotPropertyUsageFlags Source #
type InstanceCreateFun = GodotObject -> Ptr () -> IO (Ptr ()) Source #
type InstanceDestroyFun = GodotObject -> Ptr () -> Ptr () -> IO () Source #
type InstanceFreeFun = Ptr () -> IO () Source #
data GodotInstanceCreateFunc Source #
Instances
Eq GodotInstanceCreateFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative | |
Show GodotInstanceCreateFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative showsPrec :: Int -> GodotInstanceCreateFunc -> ShowS # show :: GodotInstanceCreateFunc -> String # showList :: [GodotInstanceCreateFunc] -> ShowS # | |
Storable GodotInstanceCreateFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotInstanceCreateFunc -> Int # alignment :: GodotInstanceCreateFunc -> Int # peekElemOff :: Ptr GodotInstanceCreateFunc -> Int -> IO GodotInstanceCreateFunc # pokeElemOff :: Ptr GodotInstanceCreateFunc -> Int -> GodotInstanceCreateFunc -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotInstanceCreateFunc # pokeByteOff :: Ptr b -> Int -> GodotInstanceCreateFunc -> IO () # peek :: Ptr GodotInstanceCreateFunc -> IO GodotInstanceCreateFunc # poke :: Ptr GodotInstanceCreateFunc -> GodotInstanceCreateFunc -> IO () # |
data GodotInstanceDestroyFunc Source #
Instances
Eq GodotInstanceDestroyFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative | |
Show GodotInstanceDestroyFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative showsPrec :: Int -> GodotInstanceDestroyFunc -> ShowS # show :: GodotInstanceDestroyFunc -> String # showList :: [GodotInstanceDestroyFunc] -> ShowS # | |
Storable GodotInstanceDestroyFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotInstanceDestroyFunc -> Int # alignment :: GodotInstanceDestroyFunc -> Int # peekElemOff :: Ptr GodotInstanceDestroyFunc -> Int -> IO GodotInstanceDestroyFunc # pokeElemOff :: Ptr GodotInstanceDestroyFunc -> Int -> GodotInstanceDestroyFunc -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotInstanceDestroyFunc # pokeByteOff :: Ptr b -> Int -> GodotInstanceDestroyFunc -> IO () # peek :: Ptr GodotInstanceDestroyFunc -> IO GodotInstanceDestroyFunc # poke :: Ptr GodotInstanceDestroyFunc -> GodotInstanceDestroyFunc -> IO () # |
type InstanceMethodFun = Ptr GodotVariant -> GodotObject -> Ptr () -> Ptr () -> CInt -> Ptr (Ptr GodotVariant) -> IO (Ptr GodotVariant) Source #
data GodotInstanceMethod Source #
Instances
Eq GodotInstanceMethod Source # | |
Defined in Godot.Gdnative.Internal.Gdnative (==) :: GodotInstanceMethod -> GodotInstanceMethod -> Bool # (/=) :: GodotInstanceMethod -> GodotInstanceMethod -> Bool # | |
Show GodotInstanceMethod Source # | |
Defined in Godot.Gdnative.Internal.Gdnative showsPrec :: Int -> GodotInstanceMethod -> ShowS # show :: GodotInstanceMethod -> String # showList :: [GodotInstanceMethod] -> ShowS # | |
Storable GodotInstanceMethod Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotInstanceMethod -> Int # alignment :: GodotInstanceMethod -> Int # peekElemOff :: Ptr GodotInstanceMethod -> Int -> IO GodotInstanceMethod # pokeElemOff :: Ptr GodotInstanceMethod -> Int -> GodotInstanceMethod -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotInstanceMethod # pokeByteOff :: Ptr b -> Int -> GodotInstanceMethod -> IO () # peek :: Ptr GodotInstanceMethod -> IO GodotInstanceMethod # poke :: Ptr GodotInstanceMethod -> GodotInstanceMethod -> IO () # |
newtype GodotMethodAttributes Source #
Instances
type PropertyGetFun = Ptr GodotVariant -> GodotObject -> Ptr () -> Ptr () -> IO (Ptr GodotVariant) Source #
data GodotPropertyGetFunc Source #
Instances
Eq GodotPropertyGetFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative (==) :: GodotPropertyGetFunc -> GodotPropertyGetFunc -> Bool # (/=) :: GodotPropertyGetFunc -> GodotPropertyGetFunc -> Bool # | |
Show GodotPropertyGetFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative showsPrec :: Int -> GodotPropertyGetFunc -> ShowS # show :: GodotPropertyGetFunc -> String # showList :: [GodotPropertyGetFunc] -> ShowS # | |
Storable GodotPropertyGetFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotPropertyGetFunc -> Int # alignment :: GodotPropertyGetFunc -> Int # peekElemOff :: Ptr GodotPropertyGetFunc -> Int -> IO GodotPropertyGetFunc # pokeElemOff :: Ptr GodotPropertyGetFunc -> Int -> GodotPropertyGetFunc -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotPropertyGetFunc # pokeByteOff :: Ptr b -> Int -> GodotPropertyGetFunc -> IO () # peek :: Ptr GodotPropertyGetFunc -> IO GodotPropertyGetFunc # poke :: Ptr GodotPropertyGetFunc -> GodotPropertyGetFunc -> IO () # |
type PropertySetFun = GodotObject -> Ptr () -> Ptr () -> Ptr GodotVariant -> IO () Source #
data GodotPropertySetFunc Source #
Instances
Eq GodotPropertySetFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative (==) :: GodotPropertySetFunc -> GodotPropertySetFunc -> Bool # (/=) :: GodotPropertySetFunc -> GodotPropertySetFunc -> Bool # | |
Show GodotPropertySetFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative showsPrec :: Int -> GodotPropertySetFunc -> ShowS # show :: GodotPropertySetFunc -> String # showList :: [GodotPropertySetFunc] -> ShowS # | |
Storable GodotPropertySetFunc Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotPropertySetFunc -> Int # alignment :: GodotPropertySetFunc -> Int # peekElemOff :: Ptr GodotPropertySetFunc -> Int -> IO GodotPropertySetFunc # pokeElemOff :: Ptr GodotPropertySetFunc -> Int -> GodotPropertySetFunc -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotPropertySetFunc # pokeByteOff :: Ptr b -> Int -> GodotPropertySetFunc -> IO () # peek :: Ptr GodotPropertySetFunc -> IO GodotPropertySetFunc # poke :: Ptr GodotPropertySetFunc -> GodotPropertySetFunc -> IO () # |
getOpaqueFromStruct :: forall a b. OpaqueStorable a => (ForeignPtr a -> a) -> Ptr b -> Int -> IO a Source #
setOpaqueFromStruct :: forall a b. (Coercible a (ForeignPtr a), OpaqueStorable a) => Ptr b -> a -> Int -> IO () Source #
data GodotPropertyAttributes Source #
Instances
Storable GodotPropertyAttributes Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotPropertyAttributes -> Int # alignment :: GodotPropertyAttributes -> Int # peekElemOff :: Ptr GodotPropertyAttributes -> Int -> IO GodotPropertyAttributes # pokeElemOff :: Ptr GodotPropertyAttributes -> Int -> GodotPropertyAttributes -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotPropertyAttributes # pokeByteOff :: Ptr b -> Int -> GodotPropertyAttributes -> IO () # peek :: Ptr GodotPropertyAttributes -> IO GodotPropertyAttributes # poke :: Ptr GodotPropertyAttributes -> GodotPropertyAttributes -> IO () # |
data GodotSignalArgument Source #
Instances
Storable GodotSignalArgument Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotSignalArgument -> Int # alignment :: GodotSignalArgument -> Int # peekElemOff :: Ptr GodotSignalArgument -> Int -> IO GodotSignalArgument # pokeElemOff :: Ptr GodotSignalArgument -> Int -> GodotSignalArgument -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotSignalArgument # pokeByteOff :: Ptr b -> Int -> GodotSignalArgument -> IO () # peek :: Ptr GodotSignalArgument -> IO GodotSignalArgument # poke :: Ptr GodotSignalArgument -> GodotSignalArgument -> IO () # |
data GodotSignal Source #
Instances
Storable GodotSignal Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotSignal -> Int # alignment :: GodotSignal -> Int # peekElemOff :: Ptr GodotSignal -> Int -> IO GodotSignal # pokeElemOff :: Ptr GodotSignal -> Int -> GodotSignal -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotSignal # pokeByteOff :: Ptr b -> Int -> GodotSignal -> IO () # peek :: Ptr GodotSignal -> IO GodotSignal # poke :: Ptr GodotSignal -> GodotSignal -> IO () # |
type GodotSignalPtr = Ptr GodotSignal Source #
data GodotInstanceBindingFunctions Source #
Instances
data GodotMethodArg Source #
Instances
Storable GodotMethodArg Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotMethodArg -> Int # alignment :: GodotMethodArg -> Int # peekElemOff :: Ptr GodotMethodArg -> Int -> IO GodotMethodArg # pokeElemOff :: Ptr GodotMethodArg -> Int -> GodotMethodArg -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotMethodArg # pokeByteOff :: Ptr b -> Int -> GodotMethodArg -> IO () # peek :: Ptr GodotMethodArg -> IO GodotMethodArg # poke :: Ptr GodotMethodArg -> GodotMethodArg -> IO () # |
type GodotMethodArgPtr = Ptr GodotMethodArg Source #
data GodotArvrInterfaceGdnative Source #
Instances
Storable GodotArvrInterfaceGdnative Source # | |
Defined in Godot.Gdnative.Internal.Gdnative sizeOf :: GodotArvrInterfaceGdnative -> Int # alignment :: GodotArvrInterfaceGdnative -> Int # peekElemOff :: Ptr GodotArvrInterfaceGdnative -> Int -> IO GodotArvrInterfaceGdnative # pokeElemOff :: Ptr GodotArvrInterfaceGdnative -> Int -> GodotArvrInterfaceGdnative -> IO () # peekByteOff :: Ptr b -> Int -> IO GodotArvrInterfaceGdnative # pokeByteOff :: Ptr b -> Int -> GodotArvrInterfaceGdnative -> IO () # peek :: Ptr GodotArvrInterfaceGdnative -> IO GodotArvrInterfaceGdnative # poke :: Ptr GodotArvrInterfaceGdnative -> GodotArvrInterfaceGdnative -> IO () # |
godotGdnativeExtNativescript11ApiStructRef :: IORef GodotGdnativeExtNativescript11ApiStruct Source #
initApiStructs :: GodotGdnativeInitOptions -> IO () Source #