{-# LANGUAGE ForeignFunctionInterface #-} module Irrlicht where import Foreign.GreenCard %#include "c_interface.h" %fun IGUIButtonIGUIButton :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_BUTTON) %code int result = IGUIButtonIGUIButton(environment, parent, id, EGUIET_BUTTON); %fail {result < 0} {getError();} %fun IGUIButtonSetOverrideFont :: Int -> IO () %call (int font) %code int result = IGUIButtonSetOverrideFont(font); %fail {result < 0} {getError();} %fun IGUIButtonSetImage :: Int -> IO () %call (int image) %code int result = IGUIButtonSetImage(image); %fail {result < 0} {getError();} %fun IGUIButtonSetImage :: Int -> Int -> IO () %call (int image) (int pos) %code int result = IGUIButtonSetImage(image, pos); %fail {result < 0} {getError();} %fun IGUIButtonSetPressedImage :: Int -> IO () %call (int image) %code int result = IGUIButtonSetPressedImage(image); %fail {result < 0} {getError();} %fun IGUIButtonSetPressedImage :: Int -> Int -> IO () %call (int image) (int pos) %code int result = IGUIButtonSetPressedImage(image, pos); %fail {result < 0} {getError();} %fun IGUIButtonSetSpriteBank :: Int -> IO () %call (int bank) %code int result = IGUIButtonSetSpriteBank(bank); %fail {result < 0} {getError();} %fun IGUIButtonSetSprite :: Int -> Int -> Int -> Int -> IO () %call (int state) (int index) (int color) (int loop) %code int result = IGUIButtonSetSprite(state, index, color, loop); %fail {result < 0} {getError();} %fun IGUIButtonSetIsPushButton :: Int -> IO () %call (int isPushButton) %code int result = IGUIButtonSetIsPushButton(isPushButton); %fail {result < 0} {getError();} %fun IGUIButtonSetPressed :: Int -> IO () %call (int pressed) %code int result = IGUIButtonSetPressed(pressed); %fail {result < 0} {getError();} %fun IGUIButtonIsPressed :: IO () %call %code int result = IGUIButtonIsPressed(); %fail {result < 0} {getError();} %fun IGUIButtonSetUseAlphaChannel :: Int -> IO () %call (int useAlphaChannel) %code int result = IGUIButtonSetUseAlphaChannel(useAlphaChannel); %fail {result < 0} {getError();} %fun IGUIButtonIsAlphaChannelUsed :: IO () %call %code int result = IGUIButtonIsAlphaChannelUsed(); %fail {result < 0} {getError();} %fun IGUIButtonIsPushButton :: IO () %call %code int result = IGUIButtonIsPushButton(); %fail {result < 0} {getError();} %fun IGUIButtonSetDrawBorder :: Int -> IO () %call (int border) %code int result = IGUIButtonSetDrawBorder(border); %fail {result < 0} {getError();} %fun IGUIButtonIsDrawingBorder :: IO () %call %code int result = IGUIButtonIsDrawingBorder(); %fail {result < 0} {getError();} %fun IGUIButtonSetScaleImage :: Int -> IO () %call (int scaleImage) %code int result = IGUIButtonSetScaleImage(scaleImage); %fail {result < 0} {getError();} %fun IGUIButtonIsScalingImage :: IO () %call %code int result = IGUIButtonIsScalingImage(); %fail {result < 0} {getError();} %fun ISceneUserDataSerializerISceneUserDataSerializer :: IO () %call %code int result = ISceneUserDataSerializerISceneUserDataSerializer(); %fail {result < 0} {getError();} %fun ISceneUserDataSerializerOnCreateNode :: Int -> IO () %call (int node) %code int result = ISceneUserDataSerializerOnCreateNode(node); %fail {result < 0} {getError();} %fun ISceneUserDataSerializerOnReadUserData :: Int -> Int -> IO () %call (int forSceneNode) (int userData) %code int result = ISceneUserDataSerializerOnReadUserData(forSceneNode, userData); %fail {result < 0} {getError();} %fun ISceneUserDataSerializerCreateUserData :: Int -> IO () %call (int forSceneNode) %code int result = ISceneUserDataSerializerCreateUserData(forSceneNode); %fail {result < 0} {getError();} %fun IEventReceiverIEventReceiver :: IO () %call %code int result = IEventReceiverIEventReceiver(); %fail {result < 0} {getError();} %fun IEventReceiverOnEvent :: Int -> IO () %call (int event) %code int result = IEventReceiverOnEvent(event); %fail {result < 0} {getError();} %fun IFileArchiveCreateAndOpenFile :: Int -> IO () %call (int filename) %code int result = IFileArchiveCreateAndOpenFile(filename); %fail {result < 0} {getError();} %fun IFileArchiveCreateAndOpenFile :: Int -> IO () %call (int index) %code int result = IFileArchiveCreateAndOpenFile(index); %fail {result < 0} {getError();} %fun IFileArchiveGetFileList :: IO () %call %code int result = IFileArchiveGetFileList(); %fail {result < 0} {getError();} %fun IFileArchiveGetType :: IO () %call %code int result = IFileArchiveGetType(); %fail {result < 0} {getError();} %fun IArchiveLoaderIsALoadableFileFormat :: Int -> IO () %call (int filename) %code int result = IArchiveLoaderIsALoadableFileFormat(filename); %fail {result < 0} {getError();} %fun IArchiveLoaderIsALoadableFileFormat :: Int -> IO () %call (int file) %code int result = IArchiveLoaderIsALoadableFileFormat(file); %fail {result < 0} {getError();} %fun IArchiveLoaderIsALoadableFileFormat :: Int -> IO () %call (int fileType) %code int result = IArchiveLoaderIsALoadableFileFormat(fileType); %fail {result < 0} {getError();} %fun IArchiveLoaderCreateArchive :: Int -> Int -> Int -> IO () %call (int filename) (int ignoreCase) (int ignorePaths) %code int result = IArchiveLoaderCreateArchive(filename, ignoreCase, ignorePaths); %fail {result < 0} {getError();} %fun IArchiveLoaderCreateArchive :: Int -> Int -> Int -> IO () %call (int file) (int ignoreCase) (int ignorePaths) %code int result = IArchiveLoaderCreateArchive(file, ignoreCase, ignorePaths); %fail {result < 0} {getError();} %fun ITimerITimer :: IO () %call %code int result = ITimerITimer(); %fail {result < 0} {getError();} %fun ITimerGetRealTime :: IO () %call %code int result = ITimerGetRealTime(); %fail {result < 0} {getError();} %fun ITimerGetTime :: IO () %call %code int result = ITimerGetTime(); %fail {result < 0} {getError();} %fun ITimerSetTime :: Int -> IO () %call (int time) %code int result = ITimerSetTime(time); %fail {result < 0} {getError();} %fun ITimerStop :: IO () %call %code int result = ITimerStop(); %fail {result < 0} {getError();} %fun ITimerStart :: IO () %call %code int result = ITimerStart(); %fail {result < 0} {getError();} %fun ITimerSetSpeed :: Int -> IO () %call (int speed) %code int result = ITimerSetSpeed(speed); %fail {result < 0} {getError();} %fun ITimerGetSpeed :: IO () %call %code int result = ITimerGetSpeed(); %fail {result < 0} {getError();} %fun ITimerIsStopped :: IO () %call %code int result = ITimerIsStopped(); %fail {result < 0} {getError();} %fun ITimerTick :: IO () %call %code int result = ITimerTick(); %fail {result < 0} {getError();} %fun IMeshLoaderIMeshLoader :: IO () %call %code int result = IMeshLoaderIMeshLoader(); %fail {result < 0} {getError();} %fun IMeshLoaderIsALoadableFileExtension :: Int -> IO () %call (int filename) %code int result = IMeshLoaderIsALoadableFileExtension(filename); %fail {result < 0} {getError();} %fun IMeshLoaderCreateMesh :: Int -> IO () %call (int file) %code int result = IMeshLoaderCreateMesh(file); %fail {result < 0} {getError();} %fun IGUIMeshViewerIGUIMeshViewer :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_MESH_VIEWER) %code int result = IGUIMeshViewerIGUIMeshViewer(environment, parent, id, EGUIET_MESH_VIEWER); %fail {result < 0} {getError();} %fun IGUIMeshViewerSetMesh :: Int -> IO () %call (int mesh) %code int result = IGUIMeshViewerSetMesh(mesh); %fail {result < 0} {getError();} %fun IGUIMeshViewerGetMesh :: IO () %call %code int result = IGUIMeshViewerGetMesh(); %fail {result < 0} {getError();} %fun IGUIMeshViewerSetMaterial :: Int -> IO () %call (int material) %code int result = IGUIMeshViewerSetMaterial(material); %fail {result < 0} {getError();} %fun IGUIMeshViewerGetMaterial :: IO () %call %code int result = IGUIMeshViewerGetMaterial(); %fail {result < 0} {getError();} %fun ISceneManagerISceneManager :: IO () %call %code int result = ISceneManagerISceneManager(); %fail {result < 0} {getError();} %fun ISceneManagerGetMesh :: Int -> IO () %call (int filename) %code int result = ISceneManagerGetMesh(filename); %fail {result < 0} {getError();} %fun ISceneManagerGetMesh :: Int -> IO () %call (int file) %code int result = ISceneManagerGetMesh(file); %fail {result < 0} {getError();} %fun ISceneManagerGetMeshCache :: IO () %call %code int result = ISceneManagerGetMeshCache(); %fail {result < 0} {getError();} %fun ISceneManagerGetVideoDriver :: IO () %call %code int result = ISceneManagerGetVideoDriver(); %fail {result < 0} {getError();} %fun ISceneManagerGetGUIEnvironment :: IO () %call %code int result = ISceneManagerGetGUIEnvironment(); %fail {result < 0} {getError();} %fun ISceneManagerGetFileSystem :: IO () %call %code int result = ISceneManagerGetFileSystem(); %fail {result < 0} {getError();} %fun ISceneManagerAddVolumeLightSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int id) (int subdivU) (int subdivV) (int foot) (int tail) (int position) (int rotation) (int scale) %code int result = ISceneManagerAddVolumeLightSceneNode(parent, id, subdivU, subdivV, foot, tail, position, rotation, scale); %fail {result < 0} {getError();} %fun ISceneManagerAddCubeSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int size) (int parent) (int id) (int position) (int rotation) (int scale) %code int result = ISceneManagerAddCubeSceneNode(size, parent, id, position, rotation, scale); %fail {result < 0} {getError();} %fun ISceneManagerAddSphereSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int radius) (int polyCount) (int parent) (int id) (int position) (int rotation) (int scale) %code int result = ISceneManagerAddSphereSceneNode(radius, polyCount, parent, id, position, rotation, scale); %fail {result < 0} {getError();} %fun ISceneManagerAddAnimatedMeshSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int parent) (int id) (int position) (int rotation) (int scale) (int alsoAddIfMeshPointerZero) %code int result = ISceneManagerAddAnimatedMeshSceneNode(mesh, parent, id, position, rotation, scale, alsoAddIfMeshPointerZero); %fail {result < 0} {getError();} %fun ISceneManagerAddMeshSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int parent) (int id) (int position) (int rotation) (int scale) (int alsoAddIfMeshPointerZero) %code int result = ISceneManagerAddMeshSceneNode(mesh, parent, id, position, rotation, scale, alsoAddIfMeshPointerZero); %fail {result < 0} {getError();} %fun ISceneManagerAddWaterSurfaceSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int waveHeight) (int waveSpeed) (int waveLength) (int parent) (int id) (int position) (int rotation) (int scale) %code int result = ISceneManagerAddWaterSurfaceSceneNode(mesh, waveHeight, waveSpeed, waveLength, parent, id, position, rotation, scale); %fail {result < 0} {getError();} %fun ISceneManagerAddOctreeSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int parent) (int id) (int minimalPolysPerNode) (int alsoAddIfMeshPointerZero) %code int result = ISceneManagerAddOctreeSceneNode(mesh, parent, id, minimalPolysPerNode, alsoAddIfMeshPointerZero); %fail {result < 0} {getError();} %fun ISceneManagerAddOctTreeSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int parent) (int id) (int minimalPolysPerNode) (int alsoAddIfMeshPointerZero) %code int result = ISceneManagerAddOctTreeSceneNode(mesh, parent, id, minimalPolysPerNode, alsoAddIfMeshPointerZero); %fail {result < 0} {getError();} %fun ISceneManagerAddOctreeSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int parent) (int id) (int minimalPolysPerNode) (int alsoAddIfMeshPointerZero) %code int result = ISceneManagerAddOctreeSceneNode(mesh, parent, id, minimalPolysPerNode, alsoAddIfMeshPointerZero); %fail {result < 0} {getError();} %fun ISceneManagerAddOctTreeSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int parent) (int id) (int minimalPolysPerNode) (int alsoAddIfMeshPointerZero) %code int result = ISceneManagerAddOctTreeSceneNode(mesh, parent, id, minimalPolysPerNode, alsoAddIfMeshPointerZero); %fail {result < 0} {getError();} %fun ISceneManagerAddCameraSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int position) (int lookat) (int id) (int makeActive) %code int result = ISceneManagerAddCameraSceneNode(parent, position, lookat, id, makeActive); %fail {result < 0} {getError();} %fun ISceneManagerAddCameraSceneNodeMaya :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int rotateSpeed) (int zoomSpeed) (int translationSpeed) (int id) (int makeActive) %code int result = ISceneManagerAddCameraSceneNodeMaya(parent, rotateSpeed, zoomSpeed, translationSpeed, id, makeActive); %fail {result < 0} {getError();} %fun ISceneManagerAddCameraSceneNodeFPS :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int rotateSpeed) (int moveSpeed) (int id) (int keyMapArray) (int keyMapSize) (int noVerticalMovement) (int jumpSpeed) (int invertMouse) (int makeActive) %code int result = ISceneManagerAddCameraSceneNodeFPS(parent, rotateSpeed, moveSpeed, id, keyMapArray, keyMapSize, noVerticalMovement, jumpSpeed, invertMouse, makeActive); %fail {result < 0} {getError();} %fun ISceneManagerAddLightSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int position) (int color) (int radius) (int id) %code int result = ISceneManagerAddLightSceneNode(parent, position, color, radius, id); %fail {result < 0} {getError();} %fun ISceneManagerAddBillboardSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int size) (int position) (int id) (int colorTop) (int colorBottom) %code int result = ISceneManagerAddBillboardSceneNode(parent, size, position, id, colorTop, colorBottom); %fail {result < 0} {getError();} %fun ISceneManagerAddSkyBoxSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int top) (int bottom) (int left) (int right) (int front) (int back) (int parent) (int id) %code int result = ISceneManagerAddSkyBoxSceneNode(top, bottom, left, right, front, back, parent, id); %fail {result < 0} {getError();} %fun ISceneManagerAddSkyDomeSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int texture) (int horiRes) (int vertRes) (int texturePercentage) (int spherePercentage) (int radius) (int parent) (int id) %code int result = ISceneManagerAddSkyDomeSceneNode(texture, horiRes, vertRes, texturePercentage, spherePercentage, radius, parent, id); %fail {result < 0} {getError();} %fun ISceneManagerAddParticleSystemSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int withDefaultEmitter) (int parent) (int id) (int position) (int rotation) (int scale) %code int result = ISceneManagerAddParticleSystemSceneNode(withDefaultEmitter, parent, id, position, rotation, scale); %fail {result < 0} {getError();} %fun ISceneManagerAddTerrainSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int heightMapFileName) (int parent) (int id) (int position) (int rotation) (int scale) (int vertexColor) (int maxLOD) (int patchSize) (int smoothFactor) (int addAlsoIfHeightmapEmpty) %code int result = ISceneManagerAddTerrainSceneNode(heightMapFileName, parent, id, position, rotation, scale, vertexColor, maxLOD, patchSize, smoothFactor, addAlsoIfHeightmapEmpty); %fail {result < 0} {getError();} %fun ISceneManagerAddTerrainSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int heightMapFile) (int parent) (int id) (int position) (int rotation) (int scale) (int vertexColor) (int maxLOD) (int patchSize) (int smoothFactor) (int addAlsoIfHeightmapEmpty) %code int result = ISceneManagerAddTerrainSceneNode(heightMapFile, parent, id, position, rotation, scale, vertexColor, maxLOD, patchSize, smoothFactor, addAlsoIfHeightmapEmpty); %fail {result < 0} {getError();} %fun ISceneManagerAddQuake3SceneNode :: Int -> Int -> Int -> Int -> IO () %call (int meshBuffer) (int shader) (int parent) (int id) %code int result = ISceneManagerAddQuake3SceneNode(meshBuffer, shader, parent, id); %fail {result < 0} {getError();} %fun ISceneManagerAddEmptySceneNode :: Int -> Int -> IO () %call (int parent) (int id) %code int result = ISceneManagerAddEmptySceneNode(parent, id); %fail {result < 0} {getError();} %fun ISceneManagerAddDummyTransformationSceneNode :: Int -> Int -> IO () %call (int parent) (int id) %code int result = ISceneManagerAddDummyTransformationSceneNode(parent, id); %fail {result < 0} {getError();} %fun ISceneManagerAddTextSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int font) (int text) (int color) (int parent) (int position) (int id) %code int result = ISceneManagerAddTextSceneNode(font, text, color, parent, position, id); %fail {result < 0} {getError();} %fun ISceneManagerAddBillboardTextSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int font) (int text) (int parent) (int size) (int position) (int id) (int colorTop) (int colorBottom) %code int result = ISceneManagerAddBillboardTextSceneNode(font, text, parent, size, position, id, colorTop, colorBottom); %fail {result < 0} {getError();} %fun ISceneManagerAddHillPlaneMesh :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int name) (int tileSize) (int tileCount) (int material) (int hillHeight) (int countHills) (int textureRepeatCount) %code int result = ISceneManagerAddHillPlaneMesh(name, tileSize, tileCount, material, hillHeight, countHills, textureRepeatCount); %fail {result < 0} {getError();} %fun ISceneManagerAddTerrainMesh :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int meshname) (int texture) (int heightmap) (int stretchSize) (int maxHeight) (int defaultVertexBlockSize) %code int result = ISceneManagerAddTerrainMesh(meshname, texture, heightmap, stretchSize, maxHeight, defaultVertexBlockSize); %fail {result < 0} {getError();} %fun ISceneManagerAddArrowMesh :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int name) (int vtxColor0) (int vtxColor1) (int tesselationCylinder) (int tesselationCone) (int height) (int cylinderHeight) (int width0) (int width1) %code int result = ISceneManagerAddArrowMesh(name, vtxColor0, vtxColor1, tesselationCylinder, tesselationCone, height, cylinderHeight, width0, width1); %fail {result < 0} {getError();} %fun ISceneManagerAddSphereMesh :: Int -> Int -> Int -> Int -> IO () %call (int name) (int radius) (int polyCountX) (int polyCountY) %code int result = ISceneManagerAddSphereMesh(name, radius, polyCountX, polyCountY); %fail {result < 0} {getError();} %fun ISceneManagerAddVolumeLightMesh :: Int -> Int -> Int -> Int -> Int -> IO () %call (int name) (int SubdivideU) (int SubdivideV) (int FootColor) (int TailColor) %code int result = ISceneManagerAddVolumeLightMesh(name, SubdivideU, SubdivideV, FootColor, TailColor); %fail {result < 0} {getError();} %fun ISceneManagerGetRootSceneNode :: IO () %call %code int result = ISceneManagerGetRootSceneNode(); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodeFromId :: Int -> Int -> IO () %call (int id) (int start) %code int result = ISceneManagerGetSceneNodeFromId(id, start); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodeFromName :: Int -> Int -> IO () %call (int name) (int start) %code int result = ISceneManagerGetSceneNodeFromName(name, start); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodeFromType :: Int -> Int -> IO () %call (int type) (int start) %code int result = ISceneManagerGetSceneNodeFromType(type, start); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodesFromType :: Int -> Int -> Int -> IO () %call (int type) (int outNodes) (int start) %code int result = ISceneManagerGetSceneNodesFromType(type, outNodes, start); %fail {result < 0} {getError();} %fun ISceneManagerGetActiveCamera :: IO () %call %code int result = ISceneManagerGetActiveCamera(); %fail {result < 0} {getError();} %fun ISceneManagerSetActiveCamera :: Int -> IO () %call (int camera) %code int result = ISceneManagerSetActiveCamera(camera); %fail {result < 0} {getError();} %fun ISceneManagerSetShadowColor :: Int -> IO () %call (int color) %code int result = ISceneManagerSetShadowColor(color); %fail {result < 0} {getError();} %fun ISceneManagerGetShadowColor :: IO () %call %code int result = ISceneManagerGetShadowColor(); %fail {result < 0} {getError();} %fun ISceneManagerRegisterNodeForRendering :: Int -> Int -> IO () %call (int node) (int pass) %code int result = ISceneManagerRegisterNodeForRendering(node, pass); %fail {result < 0} {getError();} %fun ISceneManagerDrawAll :: IO () %call %code int result = ISceneManagerDrawAll(); %fail {result < 0} {getError();} %fun ISceneManagerCreateRotationAnimator :: Int -> IO () %call (int rotationSpeed) %code int result = ISceneManagerCreateRotationAnimator(rotationSpeed); %fail {result < 0} {getError();} %fun ISceneManagerCreateFlyCircleAnimator :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int center) (int radius) (int speed) (int direction) (int startPosition) (int radiusEllipsoid) %code int result = ISceneManagerCreateFlyCircleAnimator(center, radius, speed, direction, startPosition, radiusEllipsoid); %fail {result < 0} {getError();} %fun ISceneManagerCreateFlyStraightAnimator :: Int -> Int -> Int -> Int -> Int -> IO () %call (int startPoint) (int endPoint) (int timeForWay) (int loop) (int pingpong) %code int result = ISceneManagerCreateFlyStraightAnimator(startPoint, endPoint, timeForWay, loop, pingpong); %fail {result < 0} {getError();} %fun ISceneManagerCreateTextureAnimator :: Int -> Int -> Int -> IO () %call (int textures) (int timePerFrame) (int loop) %code int result = ISceneManagerCreateTextureAnimator(textures, timePerFrame, loop); %fail {result < 0} {getError();} %fun ISceneManagerCreateDeleteAnimator :: Int -> IO () %call (int timeMs) %code int result = ISceneManagerCreateDeleteAnimator(timeMs); %fail {result < 0} {getError();} %fun ISceneManagerCreateCollisionResponseAnimator :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int world) (int sceneNode) (int ellipsoidRadius) (int gravityPerSecond) (int ellipsoidTranslation) (int slidingValue) %code int result = ISceneManagerCreateCollisionResponseAnimator(world, sceneNode, ellipsoidRadius, gravityPerSecond, ellipsoidTranslation, slidingValue); %fail {result < 0} {getError();} %fun ISceneManagerCreateFollowSplineAnimator :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int startTime) (int points) (int speed) (int tightness) (int loop) (int pingpong) %code int result = ISceneManagerCreateFollowSplineAnimator(startTime, points, speed, tightness, loop, pingpong); %fail {result < 0} {getError();} %fun ISceneManagerCreateTriangleSelector :: Int -> Int -> IO () %call (int mesh) (int node) %code int result = ISceneManagerCreateTriangleSelector(mesh, node); %fail {result < 0} {getError();} %fun ISceneManagerCreateTriangleSelector :: Int -> IO () %call (int node) %code int result = ISceneManagerCreateTriangleSelector(node); %fail {result < 0} {getError();} %fun ISceneManagerCreateTriangleSelectorFromBoundingBox :: Int -> IO () %call (int node) %code int result = ISceneManagerCreateTriangleSelectorFromBoundingBox(node); %fail {result < 0} {getError();} %fun ISceneManagerCreateOctreeTriangleSelector :: Int -> Int -> Int -> IO () %call (int mesh) (int node) (int minimalPolysPerNode) %code int result = ISceneManagerCreateOctreeTriangleSelector(mesh, node, minimalPolysPerNode); %fail {result < 0} {getError();} %fun ISceneManagerCreateOctTreeTriangleSelector :: Int -> Int -> Int -> IO () %call (int mesh) (int node) (int minimalPolysPerNode) %code int result = ISceneManagerCreateOctTreeTriangleSelector(mesh, node, minimalPolysPerNode); %fail {result < 0} {getError();} %fun ISceneManagerCreateMetaTriangleSelector :: IO () %call %code int result = ISceneManagerCreateMetaTriangleSelector(); %fail {result < 0} {getError();} %fun ISceneManagerCreateTerrainTriangleSelector :: Int -> Int -> IO () %call (int node) (int LOD) %code int result = ISceneManagerCreateTerrainTriangleSelector(node, LOD); %fail {result < 0} {getError();} %fun ISceneManagerAddExternalMeshLoader :: Int -> IO () %call (int externalLoader) %code int result = ISceneManagerAddExternalMeshLoader(externalLoader); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneCollisionManager :: IO () %call %code int result = ISceneManagerGetSceneCollisionManager(); %fail {result < 0} {getError();} %fun ISceneManagerGetMeshManipulator :: IO () %call %code int result = ISceneManagerGetMeshManipulator(); %fail {result < 0} {getError();} %fun ISceneManagerAddToDeletionQueue :: Int -> IO () %call (int node) %code int result = ISceneManagerAddToDeletionQueue(node); %fail {result < 0} {getError();} %fun ISceneManagerPostEventFromUser :: Int -> IO () %call (int event) %code int result = ISceneManagerPostEventFromUser(event); %fail {result < 0} {getError();} %fun ISceneManagerClear :: IO () %call %code int result = ISceneManagerClear(); %fail {result < 0} {getError();} %fun ISceneManagerGetParameters :: IO () %call %code int result = ISceneManagerGetParameters(); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodeRenderPass :: IO () %call %code int result = ISceneManagerGetSceneNodeRenderPass(); %fail {result < 0} {getError();} %fun ISceneManagerGetDefaultSceneNodeFactory :: IO () %call %code int result = ISceneManagerGetDefaultSceneNodeFactory(); %fail {result < 0} {getError();} %fun ISceneManagerRegisterSceneNodeFactory :: Int -> IO () %call (int factoryToAdd) %code int result = ISceneManagerRegisterSceneNodeFactory(factoryToAdd); %fail {result < 0} {getError();} %fun ISceneManagerGetRegisteredSceneNodeFactoryCount :: IO () %call %code int result = ISceneManagerGetRegisteredSceneNodeFactoryCount(); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodeFactory :: Int -> IO () %call (int index) %code int result = ISceneManagerGetSceneNodeFactory(index); %fail {result < 0} {getError();} %fun ISceneManagerGetDefaultSceneNodeAnimatorFactory :: IO () %call %code int result = ISceneManagerGetDefaultSceneNodeAnimatorFactory(); %fail {result < 0} {getError();} %fun ISceneManagerRegisterSceneNodeAnimatorFactory :: Int -> IO () %call (int factoryToAdd) %code int result = ISceneManagerRegisterSceneNodeAnimatorFactory(factoryToAdd); %fail {result < 0} {getError();} %fun ISceneManagerGetRegisteredSceneNodeAnimatorFactoryCount :: IO () %call %code int result = ISceneManagerGetRegisteredSceneNodeAnimatorFactoryCount(); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodeAnimatorFactory :: Int -> IO () %call (int index) %code int result = ISceneManagerGetSceneNodeAnimatorFactory(index); %fail {result < 0} {getError();} %fun ISceneManagerGetSceneNodeTypeName :: Int -> IO () %call (int type) %code int result = ISceneManagerGetSceneNodeTypeName(type); %fail {result < 0} {getError();} %fun ISceneManagerGetAnimatorTypeName :: Int -> IO () %call (int type) %code int result = ISceneManagerGetAnimatorTypeName(type); %fail {result < 0} {getError();} %fun ISceneManagerAddSceneNode :: Int -> Int -> IO () %call (int sceneNodeTypeName) (int parent) %code int result = ISceneManagerAddSceneNode(sceneNodeTypeName, parent); %fail {result < 0} {getError();} %fun ISceneManagerCreateNewSceneManager :: Int -> IO () %call (int cloneContent) %code int result = ISceneManagerCreateNewSceneManager(cloneContent); %fail {result < 0} {getError();} %fun ISceneManagerSaveScene :: Int -> Int -> IO () %call (int filename) (int userDataSerializer) %code int result = ISceneManagerSaveScene(filename, userDataSerializer); %fail {result < 0} {getError();} %fun ISceneManagerSaveScene :: Int -> Int -> IO () %call (int file) (int userDataSerializer) %code int result = ISceneManagerSaveScene(file, userDataSerializer); %fail {result < 0} {getError();} %fun ISceneManagerLoadScene :: Int -> Int -> IO () %call (int filename) (int userDataSerializer) %code int result = ISceneManagerLoadScene(filename, userDataSerializer); %fail {result < 0} {getError();} %fun ISceneManagerLoadScene :: Int -> Int -> IO () %call (int file) (int userDataSerializer) %code int result = ISceneManagerLoadScene(file, userDataSerializer); %fail {result < 0} {getError();} %fun ISceneManagerCreateMeshWriter :: Int -> IO () %call (int type) %code int result = ISceneManagerCreateMeshWriter(type); %fail {result < 0} {getError();} %fun ISceneManagerCreateSkinnedMesh :: IO () %call %code int result = ISceneManagerCreateSkinnedMesh(); %fail {result < 0} {getError();} %fun ISceneManagerSetAmbientLight :: Int -> IO () %call (int ambientColor) %code int result = ISceneManagerSetAmbientLight(ambientColor); %fail {result < 0} {getError();} %fun ISceneManagerGetAmbientLight :: IO () %call %code int result = ISceneManagerGetAmbientLight(); %fail {result < 0} {getError();} %fun ISceneManagerSetLightManager :: Int -> IO () %call (int lightManager) %code int result = ISceneManagerSetLightManager(lightManager); %fail {result < 0} {getError();} %fun ISceneManagerGetGeometryCreator :: IO () %call %code int result = ISceneManagerGetGeometryCreator(); %fail {result < 0} {getError();} %fun ISceneManagerIsCulled :: Int -> IO () %call (int node) %code int result = ISceneManagerIsCulled(node); %fail {result < 0} {getError();} %fun IVideoDriverBeginScene :: Int -> Int -> Int -> Int -> Int -> IO () %call (int backBuffer) (int zBuffer) (int color) (int videoData) (int sourceRect) %code int result = IVideoDriverBeginScene(backBuffer, zBuffer, color, videoData, sourceRect); %fail {result < 0} {getError();} %fun IVideoDriverEndScene :: IO () %call %code int result = IVideoDriverEndScene(); %fail {result < 0} {getError();} %fun IVideoDriverQueryFeature :: Int -> IO () %call (int feature) %code int result = IVideoDriverQueryFeature(feature); %fail {result < 0} {getError();} %fun IVideoDriverDisableFeature :: Int -> Int -> IO () %call (int feature) (int flag) %code int result = IVideoDriverDisableFeature(feature, flag); %fail {result < 0} {getError();} %fun IVideoDriverCheckDriverReset :: IO () %call %code int result = IVideoDriverCheckDriverReset(); %fail {result < 0} {getError();} %fun IVideoDriverSetTransform :: Int -> Int -> IO () %call (int state) (int mat) %code int result = IVideoDriverSetTransform(state, mat); %fail {result < 0} {getError();} %fun IVideoDriverGetTransform :: Int -> IO () %call (int state) %code int result = IVideoDriverGetTransform(state); %fail {result < 0} {getError();} %fun IVideoDriverGetImageLoaderCount :: IO () %call %code int result = IVideoDriverGetImageLoaderCount(); %fail {result < 0} {getError();} %fun IVideoDriverGetImageLoader :: Int -> IO () %call (int n) %code int result = IVideoDriverGetImageLoader(n); %fail {result < 0} {getError();} %fun IVideoDriverGetImageWriterCount :: IO () %call %code int result = IVideoDriverGetImageWriterCount(); %fail {result < 0} {getError();} %fun IVideoDriverGetImageWriter :: Int -> IO () %call (int n) %code int result = IVideoDriverGetImageWriter(n); %fail {result < 0} {getError();} %fun IVideoDriverSetMaterial :: Int -> IO () %call (int material) %code int result = IVideoDriverSetMaterial(material); %fail {result < 0} {getError();} %fun IVideoDriverGetTexture :: Int -> IO () %call (int filename) %code int result = IVideoDriverGetTexture(filename); %fail {result < 0} {getError();} %fun IVideoDriverGetTexture :: Int -> IO () %call (int file) %code int result = IVideoDriverGetTexture(file); %fail {result < 0} {getError();} %fun IVideoDriverGetTextureByIndex :: Int -> IO () %call (int index) %code int result = IVideoDriverGetTextureByIndex(index); %fail {result < 0} {getError();} %fun IVideoDriverGetTextureCount :: IO () %call %code int result = IVideoDriverGetTextureCount(); %fail {result < 0} {getError();} %fun IVideoDriverRenameTexture :: Int -> Int -> IO () %call (int texture) (int newName) %code int result = IVideoDriverRenameTexture(texture, newName); %fail {result < 0} {getError();} %fun IVideoDriverAddTexture :: Int -> Int -> Int -> IO () %call (int size) (int name) (int format) %code int result = IVideoDriverAddTexture(size, name, format); %fail {result < 0} {getError();} %fun IVideoDriverAddTexture :: Int -> Int -> Int -> IO () %call (int name) (int image) (int mipmapData) %code int result = IVideoDriverAddTexture(name, image, mipmapData); %fail {result < 0} {getError();} %fun IVideoDriverAddRenderTargetTexture :: Int -> Int -> Int -> IO () %call (int size) (int name) (int format) %code int result = IVideoDriverAddRenderTargetTexture(size, name, format); %fail {result < 0} {getError();} %fun IVideoDriverRemoveTexture :: Int -> IO () %call (int texture) %code int result = IVideoDriverRemoveTexture(texture); %fail {result < 0} {getError();} %fun IVideoDriverRemoveAllTextures :: IO () %call %code int result = IVideoDriverRemoveAllTextures(); %fail {result < 0} {getError();} %fun IVideoDriverRemoveHardwareBuffer :: Int -> IO () %call (int mb) %code int result = IVideoDriverRemoveHardwareBuffer(mb); %fail {result < 0} {getError();} %fun IVideoDriverRemoveAllHardwareBuffers :: IO () %call %code int result = IVideoDriverRemoveAllHardwareBuffers(); %fail {result < 0} {getError();} %fun IVideoDriverCreateOcclusionQuery :: Int -> Int -> IO () %call (int node) (int mesh) %code int result = IVideoDriverCreateOcclusionQuery(node, mesh); %fail {result < 0} {getError();} %fun IVideoDriverRemoveOcclusionQuery :: Int -> IO () %call (int node) %code int result = IVideoDriverRemoveOcclusionQuery(node); %fail {result < 0} {getError();} %fun IVideoDriverRemoveAllOcclusionQueries :: IO () %call %code int result = IVideoDriverRemoveAllOcclusionQueries(); %fail {result < 0} {getError();} %fun IVideoDriverRunOcclusionQuery :: Int -> Int -> IO () %call (int node) (int visible) %code int result = IVideoDriverRunOcclusionQuery(node, visible); %fail {result < 0} {getError();} %fun IVideoDriverRunAllOcclusionQueries :: Int -> IO () %call (int visible) %code int result = IVideoDriverRunAllOcclusionQueries(visible); %fail {result < 0} {getError();} %fun IVideoDriverUpdateOcclusionQuery :: Int -> Int -> IO () %call (int node) (int block) %code int result = IVideoDriverUpdateOcclusionQuery(node, block); %fail {result < 0} {getError();} %fun IVideoDriverUpdateAllOcclusionQueries :: Int -> IO () %call (int block) %code int result = IVideoDriverUpdateAllOcclusionQueries(block); %fail {result < 0} {getError();} %fun IVideoDriverGetOcclusionQueryResult :: Int -> IO () %call (int node) %code int result = IVideoDriverGetOcclusionQueryResult(node); %fail {result < 0} {getError();} %fun IVideoDriverMakeColorKeyTexture :: Int -> Int -> Int -> IO () %call (int texture) (int color) (int zeroTexels) %code int result = IVideoDriverMakeColorKeyTexture(texture, color, zeroTexels); %fail {result < 0} {getError();} %fun IVideoDriverMakeColorKeyTexture :: Int -> Int -> Int -> IO () %call (int texture) (int colorKeyPixelPos) (int zeroTexels) %code int result = IVideoDriverMakeColorKeyTexture(texture, colorKeyPixelPos, zeroTexels); %fail {result < 0} {getError();} %fun IVideoDriverMakeNormalMapTexture :: Int -> Int -> IO () %call (int texture) (int amplitude) %code int result = IVideoDriverMakeNormalMapTexture(texture, amplitude); %fail {result < 0} {getError();} %fun IVideoDriverSetRenderTarget :: Int -> Int -> Int -> Int -> IO () %call (int texture) (int clearBackBuffer) (int clearZBuffer) (int color) %code int result = IVideoDriverSetRenderTarget(texture, clearBackBuffer, clearZBuffer, color); %fail {result < 0} {getError();} %fun IVideoDriverSetRenderTarget :: Int -> Int -> Int -> Int -> IO () %call (int target) (int clearTarget) (int clearZBuffer) (int color) %code int result = IVideoDriverSetRenderTarget(target, clearTarget, clearZBuffer, color); %fail {result < 0} {getError();} %fun IVideoDriverSetRenderTarget :: Int -> Int -> Int -> Int -> IO () %call (int texture) (int clearBackBuffer) (int clearZBuffer) (int color) %code int result = IVideoDriverSetRenderTarget(texture, clearBackBuffer, clearZBuffer, color); %fail {result < 0} {getError();} %fun IVideoDriverSetViewPort :: Int -> IO () %call (int area) %code int result = IVideoDriverSetViewPort(area); %fail {result < 0} {getError();} %fun IVideoDriverGetViewPort :: IO () %call %code int result = IVideoDriverGetViewPort(); %fail {result < 0} {getError();} %fun IVideoDriverDrawVertexPrimitiveList :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int primCount) (int vType) (int pType) (int iType) %code int result = IVideoDriverDrawVertexPrimitiveList(vertices, vertexCount, indexList, primCount, vType, pType, iType); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DVertexPrimitiveList :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int primCount) (int vType) (int pType) (int iType) %code int result = IVideoDriverDraw2DVertexPrimitiveList(vertices, vertexCount, indexList, primCount, vType, pType, iType); %fail {result < 0} {getError();} %fun IVideoDriverDrawIndexedTriangleList :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int triangleCount) %code int result = IVideoDriverDrawIndexedTriangleList(vertices, vertexCount, indexList, triangleCount); %fail {result < 0} {getError();} %fun IVideoDriverDrawVertexPrimitiveList :: Int -> IO () %call (int EPT_TRIANGLES) %code int result = IVideoDriverDrawVertexPrimitiveList(EPT_TRIANGLES); %fail {result < 0} {getError();} %fun IVideoDriverDrawIndexedTriangleList :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int triangleCount) %code int result = IVideoDriverDrawIndexedTriangleList(vertices, vertexCount, indexList, triangleCount); %fail {result < 0} {getError();} %fun IVideoDriverDrawVertexPrimitiveList :: Int -> IO () %call (int EPT_TRIANGLES) %code int result = IVideoDriverDrawVertexPrimitiveList(EPT_TRIANGLES); %fail {result < 0} {getError();} %fun IVideoDriverDrawIndexedTriangleList :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int triangleCount) %code int result = IVideoDriverDrawIndexedTriangleList(vertices, vertexCount, indexList, triangleCount); %fail {result < 0} {getError();} %fun IVideoDriverDrawVertexPrimitiveList :: Int -> IO () %call (int EPT_TRIANGLES) %code int result = IVideoDriverDrawVertexPrimitiveList(EPT_TRIANGLES); %fail {result < 0} {getError();} %fun IVideoDriverDrawIndexedTriangleFan :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int triangleCount) %code int result = IVideoDriverDrawIndexedTriangleFan(vertices, vertexCount, indexList, triangleCount); %fail {result < 0} {getError();} %fun IVideoDriverDrawVertexPrimitiveList :: Int -> IO () %call (int EPT_TRIANGLE_FAN) %code int result = IVideoDriverDrawVertexPrimitiveList(EPT_TRIANGLE_FAN); %fail {result < 0} {getError();} %fun IVideoDriverDrawIndexedTriangleFan :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int triangleCount) %code int result = IVideoDriverDrawIndexedTriangleFan(vertices, vertexCount, indexList, triangleCount); %fail {result < 0} {getError();} %fun IVideoDriverDrawVertexPrimitiveList :: Int -> IO () %call (int EPT_TRIANGLE_FAN) %code int result = IVideoDriverDrawVertexPrimitiveList(EPT_TRIANGLE_FAN); %fail {result < 0} {getError();} %fun IVideoDriverDrawIndexedTriangleFan :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int vertexCount) (int indexList) (int triangleCount) %code int result = IVideoDriverDrawIndexedTriangleFan(vertices, vertexCount, indexList, triangleCount); %fail {result < 0} {getError();} %fun IVideoDriverDrawVertexPrimitiveList :: Int -> IO () %call (int EPT_TRIANGLE_FAN) %code int result = IVideoDriverDrawVertexPrimitiveList(EPT_TRIANGLE_FAN); %fail {result < 0} {getError();} %fun IVideoDriverDraw3DLine :: Int -> Int -> Int -> IO () %call (int start) (int end) (int color) %code int result = IVideoDriverDraw3DLine(start, end, color); %fail {result < 0} {getError();} %fun IVideoDriverDraw3DTriangle :: Int -> Int -> IO () %call (int triangle) (int color) %code int result = IVideoDriverDraw3DTriangle(triangle, color); %fail {result < 0} {getError();} %fun IVideoDriverDraw3DBox :: Int -> Int -> IO () %call (int box) (int color) %code int result = IVideoDriverDraw3DBox(box, color); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DImage :: Int -> Int -> IO () %call (int texture) (int destPos) %code int result = IVideoDriverDraw2DImage(texture, destPos); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DImage :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int texture) (int destPos) (int sourceRect) (int clipRect) (int color) (int useAlphaChannelOfTexture) %code int result = IVideoDriverDraw2DImage(texture, destPos, sourceRect, clipRect, color, useAlphaChannelOfTexture); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DImageBatch :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int texture) (int pos) (int sourceRects) (int indices) (int kerningWidth) (int clipRect) (int color) (int useAlphaChannelOfTexture) %code int result = IVideoDriverDraw2DImageBatch(texture, pos, sourceRects, indices, kerningWidth, clipRect, color, useAlphaChannelOfTexture); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DImageBatch :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int texture) (int positions) (int sourceRects) (int clipRect) (int color) (int useAlphaChannelOfTexture) %code int result = IVideoDriverDraw2DImageBatch(texture, positions, sourceRects, clipRect, color, useAlphaChannelOfTexture); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DImage :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int texture) (int destRect) (int sourceRect) (int clipRect) (int colors) (int useAlphaChannelOfTexture) %code int result = IVideoDriverDraw2DImage(texture, destRect, sourceRect, clipRect, colors, useAlphaChannelOfTexture); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DRectangle :: Int -> Int -> Int -> IO () %call (int color) (int pos) (int clip) %code int result = IVideoDriverDraw2DRectangle(color, pos, clip); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DRectangle :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int pos) (int colorLeftUp) (int colorRightUp) (int colorLeftDown) (int colorRightDown) (int clip) %code int result = IVideoDriverDraw2DRectangle(pos, colorLeftUp, colorRightUp, colorLeftDown, colorRightDown, clip); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DRectangleOutline :: Int -> Int -> IO () %call (int pos) (int color) %code int result = IVideoDriverDraw2DRectangleOutline(pos, color); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DLine :: Int -> Int -> Int -> IO () %call (int start) (int end) (int color) %code int result = IVideoDriverDraw2DLine(start, end, color); %fail {result < 0} {getError();} %fun IVideoDriverDrawPixel :: Int -> Int -> Int -> IO () %call (int x) (int y) (int color) %code int result = IVideoDriverDrawPixel(x, y, color); %fail {result < 0} {getError();} %fun IVideoDriverDraw2DPolygon :: Int -> Int -> Int -> Int -> IO () %call (int center) (int radius) (int color) (int vertexCount) %code int result = IVideoDriverDraw2DPolygon(center, radius, color, vertexCount); %fail {result < 0} {getError();} %fun IVideoDriverDrawStencilShadowVolume :: Int -> Int -> Int -> IO () %call (int triangles) (int count) (int zfail) %code int result = IVideoDriverDrawStencilShadowVolume(triangles, count, zfail); %fail {result < 0} {getError();} %fun IVideoDriverDrawStencilShadow :: Int -> Int -> Int -> Int -> Int -> IO () %call (int clearStencilBuffer) (int leftUpEdge) (int rightUpEdge) (int leftDownEdge) (int rightDownEdge) %code int result = IVideoDriverDrawStencilShadow(clearStencilBuffer, leftUpEdge, rightUpEdge, leftDownEdge, rightDownEdge); %fail {result < 0} {getError();} %fun IVideoDriverDrawMeshBuffer :: Int -> IO () %call (int mb) %code int result = IVideoDriverDrawMeshBuffer(mb); %fail {result < 0} {getError();} %fun IVideoDriverSetFog :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int color) (int fogType) (int start) (int end) (int density) (int pixelFog) (int rangeFog) %code int result = IVideoDriverSetFog(color, fogType, start, end, density, pixelFog, rangeFog); %fail {result < 0} {getError();} %fun IVideoDriverGetFog :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int color) (int fogType) (int start) (int end) (int density) (int pixelFog) (int rangeFog) %code int result = IVideoDriverGetFog(color, fogType, start, end, density, pixelFog, rangeFog); %fail {result < 0} {getError();} %fun IVideoDriverGetColorFormat :: IO () %call %code int result = IVideoDriverGetColorFormat(); %fail {result < 0} {getError();} %fun IVideoDriverGetScreenSize :: IO () %call %code int result = IVideoDriverGetScreenSize(); %fail {result < 0} {getError();} %fun IVideoDriverGetCurrentRenderTargetSize :: IO () %call %code int result = IVideoDriverGetCurrentRenderTargetSize(); %fail {result < 0} {getError();} %fun IVideoDriverGetFPS :: IO () %call %code int result = IVideoDriverGetFPS(); %fail {result < 0} {getError();} %fun IVideoDriverGetPrimitiveCountDrawn :: Int -> IO () %call (int mode) %code int result = IVideoDriverGetPrimitiveCountDrawn(mode); %fail {result < 0} {getError();} %fun IVideoDriverDeleteAllDynamicLights :: IO () %call %code int result = IVideoDriverDeleteAllDynamicLights(); %fail {result < 0} {getError();} %fun IVideoDriverAddDynamicLight :: Int -> IO () %call (int light) %code int result = IVideoDriverAddDynamicLight(light); %fail {result < 0} {getError();} %fun IVideoDriverGetMaximalDynamicLightAmount :: IO () %call %code int result = IVideoDriverGetMaximalDynamicLightAmount(); %fail {result < 0} {getError();} %fun IVideoDriverGetDynamicLightCount :: IO () %call %code int result = IVideoDriverGetDynamicLightCount(); %fail {result < 0} {getError();} %fun IVideoDriverGetDynamicLight :: Int -> IO () %call (int idx) %code int result = IVideoDriverGetDynamicLight(idx); %fail {result < 0} {getError();} %fun IVideoDriverTurnLightOn :: Int -> Int -> IO () %call (int lightIndex) (int turnOn) %code int result = IVideoDriverTurnLightOn(lightIndex, turnOn); %fail {result < 0} {getError();} %fun IVideoDriverGetName :: IO () %call %code int result = IVideoDriverGetName(); %fail {result < 0} {getError();} %fun IVideoDriverAddExternalImageLoader :: Int -> IO () %call (int loader) %code int result = IVideoDriverAddExternalImageLoader(loader); %fail {result < 0} {getError();} %fun IVideoDriverAddExternalImageWriter :: Int -> IO () %call (int writer) %code int result = IVideoDriverAddExternalImageWriter(writer); %fail {result < 0} {getError();} %fun IVideoDriverGetMaximalPrimitiveCount :: IO () %call %code int result = IVideoDriverGetMaximalPrimitiveCount(); %fail {result < 0} {getError();} %fun IVideoDriverSetTextureCreationFlag :: Int -> Int -> IO () %call (int flag) (int enabled) %code int result = IVideoDriverSetTextureCreationFlag(flag, enabled); %fail {result < 0} {getError();} %fun IVideoDriverGetTextureCreationFlag :: Int -> IO () %call (int flag) %code int result = IVideoDriverGetTextureCreationFlag(flag); %fail {result < 0} {getError();} %fun IVideoDriverCreateImageFromFile :: Int -> IO () %call (int filename) %code int result = IVideoDriverCreateImageFromFile(filename); %fail {result < 0} {getError();} %fun IVideoDriverCreateImageFromFile :: Int -> IO () %call (int file) %code int result = IVideoDriverCreateImageFromFile(file); %fail {result < 0} {getError();} %fun IVideoDriverWriteImageToFile :: Int -> Int -> Int -> IO () %call (int image) (int filename) (int param) %code int result = IVideoDriverWriteImageToFile(image, filename, param); %fail {result < 0} {getError();} %fun IVideoDriverWriteImageToFile :: Int -> Int -> Int -> IO () %call (int image) (int file) (int param) %code int result = IVideoDriverWriteImageToFile(image, file, param); %fail {result < 0} {getError();} %fun IVideoDriverCreateImageFromData :: Int -> Int -> Int -> Int -> Int -> IO () %call (int format) (int size) (int data) (int ownForeignMemory) (int deleteMemory) %code int result = IVideoDriverCreateImageFromData(format, size, data, ownForeignMemory, deleteMemory); %fail {result < 0} {getError();} %fun IVideoDriverCreateImage :: Int -> Int -> IO () %call (int format) (int size) %code int result = IVideoDriverCreateImage(format, size); %fail {result < 0} {getError();} %fun IVideoDriverCreateImage :: Int -> Int -> IO () %call (int format) (int imageToCopy) %code int result = IVideoDriverCreateImage(format, imageToCopy); %fail {result < 0} {getError();} %fun IVideoDriverCreateImage :: Int -> Int -> Int -> IO () %call (int imageToCopy) (int pos) (int size) %code int result = IVideoDriverCreateImage(imageToCopy, pos, size); %fail {result < 0} {getError();} %fun IVideoDriverCreateImage :: Int -> Int -> Int -> IO () %call (int texture) (int pos) (int size) %code int result = IVideoDriverCreateImage(texture, pos, size); %fail {result < 0} {getError();} %fun IVideoDriverOnResize :: Int -> IO () %call (int size) %code int result = IVideoDriverOnResize(size); %fail {result < 0} {getError();} %fun IVideoDriverAddMaterialRenderer :: Int -> Int -> IO () %call (int renderer) (int name) %code int result = IVideoDriverAddMaterialRenderer(renderer, name); %fail {result < 0} {getError();} %fun IVideoDriverGetMaterialRenderer :: Int -> IO () %call (int idx) %code int result = IVideoDriverGetMaterialRenderer(idx); %fail {result < 0} {getError();} %fun IVideoDriverGetMaterialRendererCount :: IO () %call %code int result = IVideoDriverGetMaterialRendererCount(); %fail {result < 0} {getError();} %fun IVideoDriverGetMaterialRendererName :: Int -> IO () %call (int idx) %code int result = IVideoDriverGetMaterialRendererName(idx); %fail {result < 0} {getError();} %fun IVideoDriverSetMaterialRendererName :: Int -> Int -> IO () %call (int idx) (int name) %code int result = IVideoDriverSetMaterialRendererName(idx, name); %fail {result < 0} {getError();} %fun IVideoDriverCreateAttributesFromMaterial :: Int -> IO () %call (int material) %code int result = IVideoDriverCreateAttributesFromMaterial(material); %fail {result < 0} {getError();} %fun IVideoDriverFillMaterialStructureFromAttributes :: Int -> Int -> IO () %call (int outMaterial) (int attributes) %code int result = IVideoDriverFillMaterialStructureFromAttributes(outMaterial, attributes); %fail {result < 0} {getError();} %fun IVideoDriverGetExposedVideoData :: IO () %call %code int result = IVideoDriverGetExposedVideoData(); %fail {result < 0} {getError();} %fun IVideoDriverGetDriverType :: IO () %call %code int result = IVideoDriverGetDriverType(); %fail {result < 0} {getError();} %fun IVideoDriverGetGPUProgrammingServices :: IO () %call %code int result = IVideoDriverGetGPUProgrammingServices(); %fail {result < 0} {getError();} %fun IVideoDriverGetMeshManipulator :: IO () %call %code int result = IVideoDriverGetMeshManipulator(); %fail {result < 0} {getError();} %fun IVideoDriverClearZBuffer :: IO () %call %code int result = IVideoDriverClearZBuffer(); %fail {result < 0} {getError();} %fun IVideoDriverCreateScreenShot :: IO () %call %code int result = IVideoDriverCreateScreenShot(); %fail {result < 0} {getError();} %fun IVideoDriverFindTexture :: Int -> IO () %call (int filename) %code int result = IVideoDriverFindTexture(filename); %fail {result < 0} {getError();} %fun IVideoDriverSetClipPlane :: Int -> Int -> Int -> IO () %call (int index) (int plane) (int enable) %code int result = IVideoDriverSetClipPlane(index, plane, enable); %fail {result < 0} {getError();} %fun IVideoDriverEnableClipPlane :: Int -> Int -> IO () %call (int index) (int enable) %code int result = IVideoDriverEnableClipPlane(index, enable); %fail {result < 0} {getError();} %fun IVideoDriverSetMinHardwareBufferVertexCount :: Int -> IO () %call (int count) %code int result = IVideoDriverSetMinHardwareBufferVertexCount(count); %fail {result < 0} {getError();} %fun IVideoDriverGetOverrideMaterial :: IO () %call %code int result = IVideoDriverGetOverrideMaterial(); %fail {result < 0} {getError();} %fun IVideoDriverGetMaterial2D :: IO () %call %code int result = IVideoDriverGetMaterial2D(); %fail {result < 0} {getError();} %fun IVideoDriverEnableMaterial2D :: Int -> IO () %call (int enable) %code int result = IVideoDriverEnableMaterial2D(enable); %fail {result < 0} {getError();} %fun IVideoDriverGetVendorInfo :: IO () %call %code int result = IVideoDriverGetVendorInfo(); %fail {result < 0} {getError();} %fun IVideoDriverSetAmbientLight :: Int -> IO () %call (int color) %code int result = IVideoDriverSetAmbientLight(color); %fail {result < 0} {getError();} %fun IVideoDriverSetAllowZWriteOnTransparent :: Int -> IO () %call (int flag) %code int result = IVideoDriverSetAllowZWriteOnTransparent(flag); %fail {result < 0} {getError();} %fun IVideoDriverGetMaxTextureSize :: IO () %call %code int result = IVideoDriverGetMaxTextureSize(); %fail {result < 0} {getError();} %fun IVideoDriverConvertColor :: Int -> Int -> Int -> Int -> Int -> IO () %call (int sP) (int sF) (int sN) (int dP) (int dF) %code int result = IVideoDriverConvertColor(sP, sF, sN, dP, dF); %fail {result < 0} {getError();} %fun ISkinnedMeshGetJointCount :: IO () %call %code int result = ISkinnedMeshGetJointCount(); %fail {result < 0} {getError();} %fun ISkinnedMeshGetJointName :: Int -> IO () %call (int number) %code int result = ISkinnedMeshGetJointName(number); %fail {result < 0} {getError();} %fun ISkinnedMeshGetJointNumber :: Int -> IO () %call (int name) %code int result = ISkinnedMeshGetJointNumber(name); %fail {result < 0} {getError();} %fun ISkinnedMeshUseAnimationFrom :: Int -> IO () %call (int mesh) %code int result = ISkinnedMeshUseAnimationFrom(mesh); %fail {result < 0} {getError();} %fun ISkinnedMeshUpdateNormalsWhenAnimating :: Int -> IO () %call (int on) %code int result = ISkinnedMeshUpdateNormalsWhenAnimating(on); %fail {result < 0} {getError();} %fun ISkinnedMeshSetInterpolationMode :: Int -> IO () %call (int mode) %code int result = ISkinnedMeshSetInterpolationMode(mode); %fail {result < 0} {getError();} %fun ISkinnedMeshAnimateMesh :: Int -> Int -> IO () %call (int frame) (int blend) %code int result = ISkinnedMeshAnimateMesh(frame, blend); %fail {result < 0} {getError();} %fun ISkinnedMeshSkinMesh :: IO () %call %code int result = ISkinnedMeshSkinMesh(); %fail {result < 0} {getError();} %fun ISkinnedMeshConvertMeshToTangents :: IO () %call %code int result = ISkinnedMeshConvertMeshToTangents(); %fail {result < 0} {getError();} %fun ISkinnedMeshSetHardwareSkinning :: Int -> IO () %call (int on) %code int result = ISkinnedMeshSetHardwareSkinning(on); %fail {result < 0} {getError();} %fun IVideoModeListGetVideoModeCount :: IO () %call %code int result = IVideoModeListGetVideoModeCount(); %fail {result < 0} {getError();} %fun IVideoModeListGetVideoModeResolution :: Int -> IO () %call (int modeNumber) %code int result = IVideoModeListGetVideoModeResolution(modeNumber); %fail {result < 0} {getError();} %fun IVideoModeListGetVideoModeResolution :: Int -> Int -> IO () %call (int minSize) (int maxSize) %code int result = IVideoModeListGetVideoModeResolution(minSize, maxSize); %fail {result < 0} {getError();} %fun IVideoModeListGetVideoModeDepth :: Int -> IO () %call (int modeNumber) %code int result = IVideoModeListGetVideoModeDepth(modeNumber); %fail {result < 0} {getError();} %fun IVideoModeListGetDesktopResolution :: IO () %call %code int result = IVideoModeListGetDesktopResolution(); %fail {result < 0} {getError();} %fun IVideoModeListGetDesktopDepth :: IO () %call %code int result = IVideoModeListGetDesktopDepth(); %fail {result < 0} {getError();} %fun IMeshCacheIMeshCache :: IO () %call %code int result = IMeshCacheIMeshCache(); %fail {result < 0} {getError();} %fun IMeshCacheAddMesh :: Int -> Int -> IO () %call (int name) (int mesh) %code int result = IMeshCacheAddMesh(name, mesh); %fail {result < 0} {getError();} %fun IMeshCacheRemoveMesh :: Int -> IO () %call (int mesh) %code int result = IMeshCacheRemoveMesh(mesh); %fail {result < 0} {getError();} %fun IMeshCacheRemoveMesh :: Int -> IO () %call (int mesh) %code int result = IMeshCacheRemoveMesh(mesh); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshCount :: IO () %call %code int result = IMeshCacheGetMeshCount(); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshIndex :: Int -> IO () %call (int mesh) %code int result = IMeshCacheGetMeshIndex(mesh); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshIndex :: Int -> IO () %call (int mesh) %code int result = IMeshCacheGetMeshIndex(mesh); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshByIndex :: Int -> IO () %call (int index) %code int result = IMeshCacheGetMeshByIndex(index); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshByFilename :: Int -> IO () %call (int filename) %code int result = IMeshCacheGetMeshByFilename(filename); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshFilename :: Int -> IO () %call (int index) %code int result = IMeshCacheGetMeshFilename(index); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshFilename :: Int -> IO () %call (int mesh) %code int result = IMeshCacheGetMeshFilename(mesh); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshFilename :: Int -> IO () %call (int mesh) %code int result = IMeshCacheGetMeshFilename(mesh); %fail {result < 0} {getError();} %fun IMeshCacheSetMeshFilename :: Int -> Int -> IO () %call (int index) (int filename) %code int result = IMeshCacheSetMeshFilename(index, filename); %fail {result < 0} {getError();} %fun IMeshCacheSetMeshFilename :: Int -> Int -> IO () %call (int mesh) (int filename) %code int result = IMeshCacheSetMeshFilename(mesh, filename); %fail {result < 0} {getError();} %fun IMeshCacheSetMeshFilename :: Int -> Int -> IO () %call (int mesh) (int filename) %code int result = IMeshCacheSetMeshFilename(mesh, filename); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshByName :: Int -> IO () %call (int name) %code int result = IMeshCacheGetMeshByName(name); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshName :: Int -> IO () %call (int index) %code int result = IMeshCacheGetMeshName(index); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshName :: Int -> IO () %call (int mesh) %code int result = IMeshCacheGetMeshName(mesh); %fail {result < 0} {getError();} %fun IMeshCacheGetMeshName :: Int -> IO () %call (int mesh) %code int result = IMeshCacheGetMeshName(mesh); %fail {result < 0} {getError();} %fun IMeshCacheRenameMesh :: Int -> Int -> IO () %call (int index) (int name) %code int result = IMeshCacheRenameMesh(index, name); %fail {result < 0} {getError();} %fun IMeshCacheRenameMesh :: Int -> Int -> IO () %call (int mesh) (int name) %code int result = IMeshCacheRenameMesh(mesh, name); %fail {result < 0} {getError();} %fun IMeshCacheRenameMesh :: Int -> Int -> IO () %call (int mesh) (int name) %code int result = IMeshCacheRenameMesh(mesh, name); %fail {result < 0} {getError();} %fun IMeshCacheIsMeshLoaded :: Int -> IO () %call (int name) %code int result = IMeshCacheIsMeshLoaded(name); %fail {result < 0} {getError();} %fun IMeshCacheClear :: IO () %call %code int result = IMeshCacheClear(); %fail {result < 0} {getError();} %fun IMeshCacheClearUnusedMeshes :: IO () %call %code int result = IMeshCacheClearUnusedMeshes(); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesIGPUProgrammingServices :: IO () %call %code int result = IGPUProgrammingServicesIGPUProgrammingServices(); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddHighLevelShaderMaterial :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgram) (int vertexShaderEntryPointName) (int vsCompileTarget) (int pixelShaderProgram) (int pixelShaderEntryPointName) (int psCompileTarget) (int geometryShaderProgram) (int geometryShaderEntryPointName) (int gsCompileTarget) (int inType) (int outType) (int verticesOut) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddHighLevelShaderMaterial(vertexShaderProgram, vertexShaderEntryPointName, vsCompileTarget, pixelShaderProgram, pixelShaderEntryPointName, psCompileTarget, geometryShaderProgram, geometryShaderEntryPointName, gsCompileTarget, inType, outType, verticesOut, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddHighLevelShaderMaterial :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgram) (int vertexShaderEntryPointName) (int vsCompileTarget) (int pixelShaderProgram) (int pixelShaderEntryPointName) (int psCompileTarget) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddHighLevelShaderMaterial(vertexShaderProgram, vertexShaderEntryPointName, vsCompileTarget, pixelShaderProgram, pixelShaderEntryPointName, psCompileTarget, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgramFileName) (int vertexShaderEntryPointName) (int vsCompileTarget) (int pixelShaderProgramFileName) (int pixelShaderEntryPointName) (int psCompileTarget) (int geometryShaderProgramFileName) (int geometryShaderEntryPointName) (int gsCompileTarget) (int inType) (int outType) (int verticesOut) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles(vertexShaderProgramFileName, vertexShaderEntryPointName, vsCompileTarget, pixelShaderProgramFileName, pixelShaderEntryPointName, psCompileTarget, geometryShaderProgramFileName, geometryShaderEntryPointName, gsCompileTarget, inType, outType, verticesOut, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgramFileName) (int vertexShaderEntryPointName) (int vsCompileTarget) (int pixelShaderProgramFileName) (int pixelShaderEntryPointName) (int psCompileTarget) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles(vertexShaderProgramFileName, vertexShaderEntryPointName, vsCompileTarget, pixelShaderProgramFileName, pixelShaderEntryPointName, psCompileTarget, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgram) (int vertexShaderEntryPointName) (int vsCompileTarget) (int pixelShaderProgram) (int pixelShaderEntryPointName) (int psCompileTarget) (int geometryShaderProgram) (int geometryShaderEntryPointName) (int gsCompileTarget) (int inType) (int outType) (int verticesOut) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles(vertexShaderProgram, vertexShaderEntryPointName, vsCompileTarget, pixelShaderProgram, pixelShaderEntryPointName, psCompileTarget, geometryShaderProgram, geometryShaderEntryPointName, gsCompileTarget, inType, outType, verticesOut, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgram) (int vertexShaderEntryPointName) (int vsCompileTarget) (int pixelShaderProgram) (int pixelShaderEntryPointName) (int psCompileTarget) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddHighLevelShaderMaterialFromFiles(vertexShaderProgram, vertexShaderEntryPointName, vsCompileTarget, pixelShaderProgram, pixelShaderEntryPointName, psCompileTarget, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddShaderMaterial :: Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgram) (int pixelShaderProgram) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddShaderMaterial(vertexShaderProgram, pixelShaderProgram, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddShaderMaterialFromFiles :: Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgram) (int pixelShaderProgram) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddShaderMaterialFromFiles(vertexShaderProgram, pixelShaderProgram, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGPUProgrammingServicesAddShaderMaterialFromFiles :: Int -> Int -> Int -> Int -> Int -> IO () %call (int vertexShaderProgramFileName) (int pixelShaderProgramFileName) (int callback) (int baseMaterial) (int userData) %code int result = IGPUProgrammingServicesAddShaderMaterialFromFiles(vertexShaderProgramFileName, pixelShaderProgramFileName, callback, baseMaterial, userData); %fail {result < 0} {getError();} %fun IGUIListBoxIGUIListBox :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_LIST_BOX) %code int result = IGUIListBoxIGUIListBox(environment, parent, id, EGUIET_LIST_BOX); %fail {result < 0} {getError();} %fun IGUIListBoxGetItemCount :: IO () %call %code int result = IGUIListBoxGetItemCount(); %fail {result < 0} {getError();} %fun IGUIListBoxGetListItem :: Int -> IO () %call (int id) %code int result = IGUIListBoxGetListItem(id); %fail {result < 0} {getError();} %fun IGUIListBoxAddItem :: Int -> IO () %call (int text) %code int result = IGUIListBoxAddItem(text); %fail {result < 0} {getError();} %fun IGUIListBoxAddItem :: Int -> Int -> IO () %call (int text) (int icon) %code int result = IGUIListBoxAddItem(text, icon); %fail {result < 0} {getError();} %fun IGUIListBoxRemoveItem :: Int -> IO () %call (int index) %code int result = IGUIListBoxRemoveItem(index); %fail {result < 0} {getError();} %fun IGUIListBoxGetIcon :: Int -> IO () %call (int index) %code int result = IGUIListBoxGetIcon(index); %fail {result < 0} {getError();} %fun IGUIListBoxSetSpriteBank :: Int -> IO () %call (int bank) %code int result = IGUIListBoxSetSpriteBank(bank); %fail {result < 0} {getError();} %fun IGUIListBoxClear :: IO () %call %code int result = IGUIListBoxClear(); %fail {result < 0} {getError();} %fun IGUIListBoxGetSelected :: IO () %call %code int result = IGUIListBoxGetSelected(); %fail {result < 0} {getError();} %fun IGUIListBoxSetSelected :: Int -> IO () %call (int index) %code int result = IGUIListBoxSetSelected(index); %fail {result < 0} {getError();} %fun IGUIListBoxSetSelected :: Int -> IO () %call (int item) %code int result = IGUIListBoxSetSelected(item); %fail {result < 0} {getError();} %fun IGUIListBoxSetAutoScrollEnabled :: Int -> IO () %call (int scroll) %code int result = IGUIListBoxSetAutoScrollEnabled(scroll); %fail {result < 0} {getError();} %fun IGUIListBoxIsAutoScrollEnabled :: IO () %call %code int result = IGUIListBoxIsAutoScrollEnabled(); %fail {result < 0} {getError();} %fun IGUIListBoxSetItemOverrideColor :: Int -> Int -> IO () %call (int index) (int color) %code int result = IGUIListBoxSetItemOverrideColor(index, color); %fail {result < 0} {getError();} %fun IGUIListBoxSetItemOverrideColor :: Int -> Int -> Int -> IO () %call (int index) (int colorType) (int color) %code int result = IGUIListBoxSetItemOverrideColor(index, colorType, color); %fail {result < 0} {getError();} %fun IGUIListBoxClearItemOverrideColor :: Int -> IO () %call (int index) %code int result = IGUIListBoxClearItemOverrideColor(index); %fail {result < 0} {getError();} %fun IGUIListBoxClearItemOverrideColor :: Int -> Int -> IO () %call (int index) (int colorType) %code int result = IGUIListBoxClearItemOverrideColor(index, colorType); %fail {result < 0} {getError();} %fun IGUIListBoxHasItemOverrideColor :: Int -> Int -> IO () %call (int index) (int colorType) %code int result = IGUIListBoxHasItemOverrideColor(index, colorType); %fail {result < 0} {getError();} %fun IGUIListBoxGetItemOverrideColor :: Int -> Int -> IO () %call (int index) (int colorType) %code int result = IGUIListBoxGetItemOverrideColor(index, colorType); %fail {result < 0} {getError();} %fun IGUIListBoxGetItemDefaultColor :: Int -> IO () %call (int colorType) %code int result = IGUIListBoxGetItemDefaultColor(colorType); %fail {result < 0} {getError();} %fun IGUIListBoxSetItem :: Int -> Int -> Int -> IO () %call (int index) (int text) (int icon) %code int result = IGUIListBoxSetItem(index, text, icon); %fail {result < 0} {getError();} %fun IGUIListBoxInsertItem :: Int -> Int -> Int -> IO () %call (int index) (int text) (int icon) %code int result = IGUIListBoxInsertItem(index, text, icon); %fail {result < 0} {getError();} %fun IGUIListBoxSwapItems :: Int -> Int -> IO () %call (int index1) (int index2) %code int result = IGUIListBoxSwapItems(index1, index2); %fail {result < 0} {getError();} %fun IGUIListBoxSetItemHeight :: Int -> IO () %call (int height) %code int result = IGUIListBoxSetItemHeight(height); %fail {result < 0} {getError();} %fun IGUIListBoxSetDrawBackground :: Int -> IO () %call (int draw) %code int result = IGUIListBoxSetDrawBackground(draw); %fail {result < 0} {getError();} %fun IGUIEditBoxIGUIEditBox :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_EDIT_BOX) %code int result = IGUIEditBoxIGUIEditBox(environment, parent, id, EGUIET_EDIT_BOX); %fail {result < 0} {getError();} %fun IGUIEditBoxSetOverrideFont :: Int -> IO () %call (int font) %code int result = IGUIEditBoxSetOverrideFont(font); %fail {result < 0} {getError();} %fun IGUIEditBoxSetOverrideColor :: Int -> IO () %call (int color) %code int result = IGUIEditBoxSetOverrideColor(color); %fail {result < 0} {getError();} %fun IGUIEditBoxGetOverrideColor :: IO () %call %code int result = IGUIEditBoxGetOverrideColor(); %fail {result < 0} {getError();} %fun IGUIEditBoxEnableOverrideColor :: Int -> IO () %call (int enable) %code int result = IGUIEditBoxEnableOverrideColor(enable); %fail {result < 0} {getError();} %fun IGUIEditBoxIsOverrideColorEnabled :: IO () %call %code int result = IGUIEditBoxIsOverrideColorEnabled(); %fail {result < 0} {getError();} %fun IGUIEditBoxSetDrawBorder :: Int -> IO () %call (int border) %code int result = IGUIEditBoxSetDrawBorder(border); %fail {result < 0} {getError();} %fun IGUIEditBoxSetTextAlignment :: Int -> Int -> IO () %call (int horizontal) (int vertical) %code int result = IGUIEditBoxSetTextAlignment(horizontal, vertical); %fail {result < 0} {getError();} %fun IGUIEditBoxSetWordWrap :: Int -> IO () %call (int enable) %code int result = IGUIEditBoxSetWordWrap(enable); %fail {result < 0} {getError();} %fun IGUIEditBoxIsWordWrapEnabled :: IO () %call %code int result = IGUIEditBoxIsWordWrapEnabled(); %fail {result < 0} {getError();} %fun IGUIEditBoxSetMultiLine :: Int -> IO () %call (int enable) %code int result = IGUIEditBoxSetMultiLine(enable); %fail {result < 0} {getError();} %fun IGUIEditBoxIsMultiLineEnabled :: IO () %call %code int result = IGUIEditBoxIsMultiLineEnabled(); %fail {result < 0} {getError();} %fun IGUIEditBoxSetAutoScroll :: Int -> IO () %call (int enable) %code int result = IGUIEditBoxSetAutoScroll(enable); %fail {result < 0} {getError();} %fun IGUIEditBoxIsAutoScrollEnabled :: IO () %call %code int result = IGUIEditBoxIsAutoScrollEnabled(); %fail {result < 0} {getError();} %fun IGUIEditBoxSetPasswordBox :: Int -> Int -> IO () %call (int passwordBox) (int passwordChar) %code int result = IGUIEditBoxSetPasswordBox(passwordBox, passwordChar); %fail {result < 0} {getError();} %fun IGUIEditBoxIsPasswordBox :: IO () %call %code int result = IGUIEditBoxIsPasswordBox(); %fail {result < 0} {getError();} %fun IGUIEditBoxGetTextDimension :: IO () %call %code int result = IGUIEditBoxGetTextDimension(); %fail {result < 0} {getError();} %fun IGUIEditBoxSetMax :: Int -> IO () %call (int max) %code int result = IGUIEditBoxSetMax(max); %fail {result < 0} {getError();} %fun IGUIEditBoxGetMax :: IO () %call %code int result = IGUIEditBoxGetMax(); %fail {result < 0} {getError();} %fun ITriangleSelectorITriangleSelector :: IO () %call %code int result = ITriangleSelectorITriangleSelector(); %fail {result < 0} {getError();} %fun ITriangleSelectorGetTriangleCount :: IO () %call %code int result = ITriangleSelectorGetTriangleCount(); %fail {result < 0} {getError();} %fun ITriangleSelectorGetTriangles :: Int -> Int -> Int -> Int -> IO () %call (int triangles) (int arraySize) (int outTriangleCount) (int transform) %code int result = ITriangleSelectorGetTriangles(triangles, arraySize, outTriangleCount, transform); %fail {result < 0} {getError();} %fun ITriangleSelectorGetTriangles :: Int -> Int -> Int -> Int -> Int -> IO () %call (int triangles) (int arraySize) (int outTriangleCount) (int box) (int transform) %code int result = ITriangleSelectorGetTriangles(triangles, arraySize, outTriangleCount, box, transform); %fail {result < 0} {getError();} %fun ITriangleSelectorGetTriangles :: Int -> Int -> Int -> Int -> Int -> IO () %call (int triangles) (int arraySize) (int outTriangleCount) (int line) (int transform) %code int result = ITriangleSelectorGetTriangles(triangles, arraySize, outTriangleCount, line, transform); %fail {result < 0} {getError();} %fun ITriangleSelectorGetSceneNodeForTriangle :: Int -> IO () %call (int triangleIndex) %code int result = ITriangleSelectorGetSceneNodeForTriangle(triangleIndex); %fail {result < 0} {getError();} %fun IGUISkinGetColor :: Int -> IO () %call (int color) %code int result = IGUISkinGetColor(color); %fail {result < 0} {getError();} %fun IGUISkinSetColor :: Int -> Int -> IO () %call (int which) (int newColor) %code int result = IGUISkinSetColor(which, newColor); %fail {result < 0} {getError();} %fun IGUISkinGetSize :: Int -> IO () %call (int size) %code int result = IGUISkinGetSize(size); %fail {result < 0} {getError();} %fun IGUISkinGetDefaultText :: Int -> IO () %call (int text) %code int result = IGUISkinGetDefaultText(text); %fail {result < 0} {getError();} %fun IGUISkinSetDefaultText :: Int -> Int -> IO () %call (int which) (int newText) %code int result = IGUISkinSetDefaultText(which, newText); %fail {result < 0} {getError();} %fun IGUISkinSetSize :: Int -> Int -> IO () %call (int which) (int size) %code int result = IGUISkinSetSize(which, size); %fail {result < 0} {getError();} %fun IGUISkinGetFont :: Int -> IO () %call (int which) %code int result = IGUISkinGetFont(which); %fail {result < 0} {getError();} %fun IGUISkinSetFont :: Int -> Int -> IO () %call (int font) (int which) %code int result = IGUISkinSetFont(font, which); %fail {result < 0} {getError();} %fun IGUISkinGetSpriteBank :: IO () %call %code int result = IGUISkinGetSpriteBank(); %fail {result < 0} {getError();} %fun IGUISkinSetSpriteBank :: Int -> IO () %call (int bank) %code int result = IGUISkinSetSpriteBank(bank); %fail {result < 0} {getError();} %fun IGUISkinGetIcon :: Int -> IO () %call (int icon) %code int result = IGUISkinGetIcon(icon); %fail {result < 0} {getError();} %fun IGUISkinSetIcon :: Int -> Int -> IO () %call (int icon) (int index) %code int result = IGUISkinSetIcon(icon, index); %fail {result < 0} {getError();} %fun IGUISkinDraw3DButtonPaneStandard :: Int -> Int -> Int -> IO () %call (int element) (int rect) (int clip) %code int result = IGUISkinDraw3DButtonPaneStandard(element, rect, clip); %fail {result < 0} {getError();} %fun IGUISkinDraw3DButtonPanePressed :: Int -> Int -> Int -> IO () %call (int element) (int rect) (int clip) %code int result = IGUISkinDraw3DButtonPanePressed(element, rect, clip); %fail {result < 0} {getError();} %fun IGUISkinDraw3DSunkenPane :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int element) (int bgcolor) (int flat) (int fillBackGround) (int rect) (int clip) %code int result = IGUISkinDraw3DSunkenPane(element, bgcolor, flat, fillBackGround, rect, clip); %fail {result < 0} {getError();} %fun IGUISkinDraw3DWindowBackground :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int element) (int drawTitleBar) (int titleBarColor) (int rect) (int clip) (int checkClientArea) %code int result = IGUISkinDraw3DWindowBackground(element, drawTitleBar, titleBarColor, rect, clip, checkClientArea); %fail {result < 0} {getError();} %fun IGUISkinDraw3DMenuPane :: Int -> Int -> Int -> IO () %call (int element) (int rect) (int clip) %code int result = IGUISkinDraw3DMenuPane(element, rect, clip); %fail {result < 0} {getError();} %fun IGUISkinDraw3DToolBar :: Int -> Int -> Int -> IO () %call (int element) (int rect) (int clip) %code int result = IGUISkinDraw3DToolBar(element, rect, clip); %fail {result < 0} {getError();} %fun IGUISkinDraw3DTabButton :: Int -> Int -> Int -> Int -> Int -> IO () %call (int element) (int active) (int rect) (int clip) (int alignment) %code int result = IGUISkinDraw3DTabButton(element, active, rect, clip, alignment); %fail {result < 0} {getError();} %fun IGUISkinDraw3DTabBody :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int element) (int border) (int background) (int rect) (int clip) (int tabHeight) (int alignment) %code int result = IGUISkinDraw3DTabBody(element, border, background, rect, clip, tabHeight, alignment); %fail {result < 0} {getError();} %fun IGUISkinDrawIcon :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int element) (int icon) (int position) (int starttime) (int currenttime) (int loop) (int clip) %code int result = IGUISkinDrawIcon(element, icon, position, starttime, currenttime, loop, clip); %fail {result < 0} {getError();} %fun IGUISkinDraw2DRectangle :: Int -> Int -> Int -> Int -> IO () %call (int element) (int color) (int pos) (int clip) %code int result = IGUISkinDraw2DRectangle(element, color, pos, clip); %fail {result < 0} {getError();} %fun IGUISkinGetType :: IO () %call %code int result = IGUISkinGetType(); %fail {result < 0} {getError();} %fun IDummyTransformationSceneNodeIDummyTransformationSceneNode :: Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int parent) %code int result = IDummyTransformationSceneNodeIDummyTransformationSceneNode(parent, mgr, parent); %fail {result < 0} {getError();} %fun IDummyTransformationSceneNodeGetRelativeTransformationMatrix :: IO () %call %code int result = IDummyTransformationSceneNodeGetRelativeTransformationMatrix(); %fail {result < 0} {getError();} %fun IFileSystemCreateAndOpenFile :: Int -> IO () %call (int filename) %code int result = IFileSystemCreateAndOpenFile(filename); %fail {result < 0} {getError();} %fun IFileSystemCreateMemoryReadFile :: Int -> Int -> Int -> Int -> IO () %call (int memory) (int len) (int fileName) (int deleteMemoryWhenDropped) %code int result = IFileSystemCreateMemoryReadFile(memory, len, fileName, deleteMemoryWhenDropped); %fail {result < 0} {getError();} %fun IFileSystemCreateLimitReadFile :: Int -> Int -> Int -> Int -> IO () %call (int fileName) (int alreadyOpenedFile) (int pos) (int areaSize) %code int result = IFileSystemCreateLimitReadFile(fileName, alreadyOpenedFile, pos, areaSize); %fail {result < 0} {getError();} %fun IFileSystemCreateMemoryWriteFile :: Int -> Int -> Int -> Int -> IO () %call (int memory) (int len) (int fileName) (int deleteMemoryWhenDropped) %code int result = IFileSystemCreateMemoryWriteFile(memory, len, fileName, deleteMemoryWhenDropped); %fail {result < 0} {getError();} %fun IFileSystemCreateAndWriteFile :: Int -> Int -> IO () %call (int filename) (int append) %code int result = IFileSystemCreateAndWriteFile(filename, append); %fail {result < 0} {getError();} %fun IFileSystemAddFileArchive :: Int -> Int -> Int -> Int -> Int -> IO () %call (int filename) (int ignoreCase) (int ignorePaths) (int archiveType) (int password) %code int result = IFileSystemAddFileArchive(filename, ignoreCase, ignorePaths, archiveType, password); %fail {result < 0} {getError();} %fun IFileSystemAddArchiveLoader :: Int -> IO () %call (int loader) %code int result = IFileSystemAddArchiveLoader(loader); %fail {result < 0} {getError();} %fun IFileSystemGetFileArchiveCount :: IO () %call %code int result = IFileSystemGetFileArchiveCount(); %fail {result < 0} {getError();} %fun IFileSystemRemoveFileArchive :: Int -> IO () %call (int index) %code int result = IFileSystemRemoveFileArchive(index); %fail {result < 0} {getError();} %fun IFileSystemRemoveFileArchive :: Int -> IO () %call (int filename) %code int result = IFileSystemRemoveFileArchive(filename); %fail {result < 0} {getError();} %fun IFileSystemMoveFileArchive :: Int -> Int -> IO () %call (int sourceIndex) (int relative) %code int result = IFileSystemMoveFileArchive(sourceIndex, relative); %fail {result < 0} {getError();} %fun IFileSystemGetFileArchive :: Int -> IO () %call (int index) %code int result = IFileSystemGetFileArchive(index); %fail {result < 0} {getError();} %fun IFileSystemAddZipFileArchive :: Int -> Int -> Int -> IO () %call (int filename) (int ignoreCase) (int ignorePaths) %code int result = IFileSystemAddZipFileArchive(filename, ignoreCase, ignorePaths); %fail {result < 0} {getError();} %fun IFileSystemAddFolderFileArchive :: Int -> Int -> Int -> IO () %call (int filename) (int ignoreCase) (int ignorePaths) %code int result = IFileSystemAddFolderFileArchive(filename, ignoreCase, ignorePaths); %fail {result < 0} {getError();} %fun IFileSystemAddPakFileArchive :: Int -> Int -> Int -> IO () %call (int filename) (int ignoreCase) (int ignorePaths) %code int result = IFileSystemAddPakFileArchive(filename, ignoreCase, ignorePaths); %fail {result < 0} {getError();} %fun IFileSystemGetWorkingDirectory :: IO () %call %code int result = IFileSystemGetWorkingDirectory(); %fail {result < 0} {getError();} %fun IFileSystemChangeWorkingDirectoryTo :: Int -> IO () %call (int newDirectory) %code int result = IFileSystemChangeWorkingDirectoryTo(newDirectory); %fail {result < 0} {getError();} %fun IFileSystemGetAbsolutePath :: Int -> IO () %call (int filename) %code int result = IFileSystemGetAbsolutePath(filename); %fail {result < 0} {getError();} %fun IFileSystemGetFileDir :: Int -> IO () %call (int filename) %code int result = IFileSystemGetFileDir(filename); %fail {result < 0} {getError();} %fun IFileSystemGetFileBasename :: Int -> Int -> IO () %call (int filename) (int keepExtension) %code int result = IFileSystemGetFileBasename(filename, keepExtension); %fail {result < 0} {getError();} %fun IFileSystemFlattenFilename :: Int -> Int -> IO () %call (int directory) (int root) %code int result = IFileSystemFlattenFilename(directory, root); %fail {result < 0} {getError();} %fun IFileSystemCreateFileList :: IO () %call %code int result = IFileSystemCreateFileList(); %fail {result < 0} {getError();} %fun IFileSystemCreateEmptyFileList :: Int -> Int -> Int -> IO () %call (int path) (int ignoreCase) (int ignorePaths) %code int result = IFileSystemCreateEmptyFileList(path, ignoreCase, ignorePaths); %fail {result < 0} {getError();} %fun IFileSystemSetFileListSystem :: Int -> IO () %call (int listType) %code int result = IFileSystemSetFileListSystem(listType); %fail {result < 0} {getError();} %fun IFileSystemExistFile :: Int -> IO () %call (int filename) %code int result = IFileSystemExistFile(filename); %fail {result < 0} {getError();} %fun IFileSystemCreateXMLReader :: Int -> IO () %call (int filename) %code int result = IFileSystemCreateXMLReader(filename); %fail {result < 0} {getError();} %fun IFileSystemCreateXMLReader :: Int -> IO () %call (int file) %code int result = IFileSystemCreateXMLReader(file); %fail {result < 0} {getError();} %fun IFileSystemCreateXMLReaderUTF8 :: Int -> IO () %call (int filename) %code int result = IFileSystemCreateXMLReaderUTF8(filename); %fail {result < 0} {getError();} %fun IFileSystemCreateXMLReaderUTF8 :: Int -> IO () %call (int file) %code int result = IFileSystemCreateXMLReaderUTF8(file); %fail {result < 0} {getError();} %fun IFileSystemCreateXMLWriter :: Int -> IO () %call (int filename) %code int result = IFileSystemCreateXMLWriter(filename); %fail {result < 0} {getError();} %fun IFileSystemCreateXMLWriter :: Int -> IO () %call (int file) %code int result = IFileSystemCreateXMLWriter(file); %fail {result < 0} {getError();} %fun IFileSystemCreateEmptyAttributes :: Int -> IO () %call (int driver) %code int result = IFileSystemCreateEmptyAttributes(driver); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetVertexBuffer :: IO () %call %code int result = IDynamicMeshBufferGetVertexBuffer(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetIndexBuffer :: IO () %call %code int result = IDynamicMeshBufferGetIndexBuffer(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferSetVertexBuffer :: Int -> IO () %call (int vertexBuffer) %code int result = IDynamicMeshBufferSetVertexBuffer(vertexBuffer); %fail {result < 0} {getError();} %fun IDynamicMeshBufferSetIndexBuffer :: Int -> IO () %call (int indexBuffer) %code int result = IDynamicMeshBufferSetIndexBuffer(indexBuffer); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetMaterial :: IO () %call %code int result = IDynamicMeshBufferGetMaterial(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetMaterial :: IO () %call %code int result = IDynamicMeshBufferGetMaterial(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetBoundingBox :: IO () %call %code int result = IDynamicMeshBufferGetBoundingBox(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferSetBoundingBox :: Int -> IO () %call (int box) %code int result = IDynamicMeshBufferSetBoundingBox(box); %fail {result < 0} {getError();} %fun IDynamicMeshBufferRecalculateBoundingBox :: IO () %call %code int result = IDynamicMeshBufferRecalculateBoundingBox(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferAppend :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int numVertices) (int indices) (int numIndices) %code int result = IDynamicMeshBufferAppend(vertices, numVertices, indices, numIndices); %fail {result < 0} {getError();} %fun IDynamicMeshBufferAppend :: Int -> IO () %call (int other) %code int result = IDynamicMeshBufferAppend(other); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetHardwareMappingHint_Vertex :: IO () %call %code int result = IDynamicMeshBufferGetHardwareMappingHint_Vertex(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetHardwareMappingHint_Index :: IO () %call %code int result = IDynamicMeshBufferGetHardwareMappingHint_Index(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferSetHardwareMappingHint :: Int -> Int -> IO () %call (int NewMappingHint) (int Buffer) %code int result = IDynamicMeshBufferSetHardwareMappingHint(NewMappingHint, Buffer); %fail {result < 0} {getError();} %fun IDynamicMeshBufferSetDirty :: Int -> IO () %call (int Buffer) %code int result = IDynamicMeshBufferSetDirty(Buffer); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetChangedID_Vertex :: IO () %call %code int result = IDynamicMeshBufferGetChangedID_Vertex(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetChangedID_Index :: IO () %call %code int result = IDynamicMeshBufferGetChangedID_Index(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetVertexType :: IO () %call %code int result = IDynamicMeshBufferGetVertexType(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetVertices :: IO () %call %code int result = IDynamicMeshBufferGetVertices(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetVertices :: IO () %call %code int result = IDynamicMeshBufferGetVertices(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetVertexCount :: IO () %call %code int result = IDynamicMeshBufferGetVertexCount(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetIndexType :: IO () %call %code int result = IDynamicMeshBufferGetIndexType(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetIndices :: IO () %call %code int result = IDynamicMeshBufferGetIndices(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetIndices :: IO () %call %code int result = IDynamicMeshBufferGetIndices(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetIndexCount :: IO () %call %code int result = IDynamicMeshBufferGetIndexCount(); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetPosition :: Int -> IO () %call (int i) %code int result = IDynamicMeshBufferGetPosition(i); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetPosition :: Int -> IO () %call (int i) %code int result = IDynamicMeshBufferGetPosition(i); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetTCoords :: Int -> IO () %call (int i) %code int result = IDynamicMeshBufferGetTCoords(i); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetTCoords :: Int -> IO () %call (int i) %code int result = IDynamicMeshBufferGetTCoords(i); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetNormal :: Int -> IO () %call (int i) %code int result = IDynamicMeshBufferGetNormal(i); %fail {result < 0} {getError();} %fun IDynamicMeshBufferGetNormal :: Int -> IO () %call (int i) %code int result = IDynamicMeshBufferGetNormal(i); %fail {result < 0} {getError();} %fun IMeshBufferGetMaterial :: IO () %call %code int result = IMeshBufferGetMaterial(); %fail {result < 0} {getError();} %fun IMeshBufferGetMaterial :: IO () %call %code int result = IMeshBufferGetMaterial(); %fail {result < 0} {getError();} %fun IMeshBufferGetVertexType :: IO () %call %code int result = IMeshBufferGetVertexType(); %fail {result < 0} {getError();} %fun IMeshBufferGetVertices :: IO () %call %code int result = IMeshBufferGetVertices(); %fail {result < 0} {getError();} %fun IMeshBufferGetVertices :: IO () %call %code int result = IMeshBufferGetVertices(); %fail {result < 0} {getError();} %fun IMeshBufferGetVertexCount :: IO () %call %code int result = IMeshBufferGetVertexCount(); %fail {result < 0} {getError();} %fun IMeshBufferGetIndexType :: IO () %call %code int result = IMeshBufferGetIndexType(); %fail {result < 0} {getError();} %fun IMeshBufferGetIndices :: IO () %call %code int result = IMeshBufferGetIndices(); %fail {result < 0} {getError();} %fun IMeshBufferGetIndices :: IO () %call %code int result = IMeshBufferGetIndices(); %fail {result < 0} {getError();} %fun IMeshBufferGetIndexCount :: IO () %call %code int result = IMeshBufferGetIndexCount(); %fail {result < 0} {getError();} %fun IMeshBufferGetBoundingBox :: IO () %call %code int result = IMeshBufferGetBoundingBox(); %fail {result < 0} {getError();} %fun IMeshBufferSetBoundingBox :: Int -> IO () %call (int box) %code int result = IMeshBufferSetBoundingBox(box); %fail {result < 0} {getError();} %fun IMeshBufferRecalculateBoundingBox :: IO () %call %code int result = IMeshBufferRecalculateBoundingBox(); %fail {result < 0} {getError();} %fun IMeshBufferGetPosition :: Int -> IO () %call (int i) %code int result = IMeshBufferGetPosition(i); %fail {result < 0} {getError();} %fun IMeshBufferGetPosition :: Int -> IO () %call (int i) %code int result = IMeshBufferGetPosition(i); %fail {result < 0} {getError();} %fun IMeshBufferGetNormal :: Int -> IO () %call (int i) %code int result = IMeshBufferGetNormal(i); %fail {result < 0} {getError();} %fun IMeshBufferGetNormal :: Int -> IO () %call (int i) %code int result = IMeshBufferGetNormal(i); %fail {result < 0} {getError();} %fun IMeshBufferGetTCoords :: Int -> IO () %call (int i) %code int result = IMeshBufferGetTCoords(i); %fail {result < 0} {getError();} %fun IMeshBufferGetTCoords :: Int -> IO () %call (int i) %code int result = IMeshBufferGetTCoords(i); %fail {result < 0} {getError();} %fun IMeshBufferAppend :: Int -> Int -> Int -> Int -> IO () %call (int vertices) (int numVertices) (int indices) (int numIndices) %code int result = IMeshBufferAppend(vertices, numVertices, indices, numIndices); %fail {result < 0} {getError();} %fun IMeshBufferAppend :: Int -> IO () %call (int other) %code int result = IMeshBufferAppend(other); %fail {result < 0} {getError();} %fun IMeshBufferGetHardwareMappingHint_Vertex :: IO () %call %code int result = IMeshBufferGetHardwareMappingHint_Vertex(); %fail {result < 0} {getError();} %fun IMeshBufferGetHardwareMappingHint_Index :: IO () %call %code int result = IMeshBufferGetHardwareMappingHint_Index(); %fail {result < 0} {getError();} %fun IMeshBufferSetHardwareMappingHint :: Int -> Int -> IO () %call (int newMappingHint) (int buffer) %code int result = IMeshBufferSetHardwareMappingHint(newMappingHint, buffer); %fail {result < 0} {getError();} %fun IMeshBufferSetDirty :: Int -> IO () %call (int buffer) %code int result = IMeshBufferSetDirty(buffer); %fail {result < 0} {getError();} %fun IMeshBufferGetChangedID_Vertex :: IO () %call %code int result = IMeshBufferGetChangedID_Vertex(); %fail {result < 0} {getError();} %fun IMeshBufferGetChangedID_Index :: IO () %call %code int result = IMeshBufferGetChangedID_Index(); %fail {result < 0} {getError();} %fun SMaterialSMaterial :: IO () %call %code int result = SMaterialSMaterial(); %fail {result < 0} {getError();} %fun SMaterialSMaterial :: Int -> IO () %call (int other) %code int result = SMaterialSMaterial(other); %fail {result < 0} {getError();} %fun SMaterialGetTextureMatrix :: Int -> IO () %call (int i) %code int result = SMaterialGetTextureMatrix(i); %fail {result < 0} {getError();} %fun SMaterialGetTextureMatrix :: Int -> IO () %call (int i) %code int result = SMaterialGetTextureMatrix(i); %fail {result < 0} {getError();} %fun SMaterialSetTextureMatrix :: Int -> Int -> IO () %call (int i) (int mat) %code int result = SMaterialSetTextureMatrix(i, mat); %fail {result < 0} {getError();} %fun SMaterialSetTextureMatrix :: IO () %call %code int result = SMaterialSetTextureMatrix(); %fail {result < 0} {getError();} %fun SMaterialGetTexture :: Int -> IO () %call (int i) %code int result = SMaterialGetTexture(i); %fail {result < 0} {getError();} %fun SMaterialSetTexture :: Int -> Int -> IO () %call (int i) (int tex) %code int result = SMaterialSetTexture(i, tex); %fail {result < 0} {getError();} %fun SMaterialSetFlag :: Int -> Int -> IO () %call (int flag) (int value) %code int result = SMaterialSetFlag(flag, value); %fail {result < 0} {getError();} %fun SMaterialSwitch :: IO () %call %code int result = SMaterialSwitch(); %fail {result < 0} {getError();} %fun SMaterialGetFlag :: Int -> IO () %call (int flag) %code int result = SMaterialGetFlag(flag); %fail {result < 0} {getError();} %fun SMaterialSwitch :: IO () %call %code int result = SMaterialSwitch(); %fail {result < 0} {getError();} %fun SMaterialIsTransparent :: IO () %call %code int result = SMaterialIsTransparent(); %fail {result < 0} {getError();} %fun IMaterialRendererOnSetMaterial :: Int -> Int -> Int -> Int -> IO () %call (int material) (int lastMaterial) (int resetAllRenderstates) (int services) %code int result = IMaterialRendererOnSetMaterial(material, lastMaterial, resetAllRenderstates, services); %fail {result < 0} {getError();} %fun IMaterialRendererOnRender :: Int -> Int -> IO () %call (int service) (int vtxtype) %code int result = IMaterialRendererOnRender(service, vtxtype); %fail {result < 0} {getError();} %fun IMaterialRendererOnUnsetMaterial :: IO () %call %code int result = IMaterialRendererOnUnsetMaterial(); %fail {result < 0} {getError();} %fun IMaterialRendererIsTransparent :: IO () %call %code int result = IMaterialRendererIsTransparent(); %fail {result < 0} {getError();} %fun IMaterialRendererGetRenderCapability :: IO () %call %code int result = IMaterialRendererGetRenderCapability(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorFactoryISceneNodeAnimatorFactory :: IO () %call %code int result = ISceneNodeAnimatorFactoryISceneNodeAnimatorFactory(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorFactoryCreateSceneNodeAnimator :: Int -> Int -> IO () %call (int type) (int target) %code int result = ISceneNodeAnimatorFactoryCreateSceneNodeAnimator(type, target); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorFactoryCreateSceneNodeAnimator :: Int -> Int -> IO () %call (int typeName) (int target) %code int result = ISceneNodeAnimatorFactoryCreateSceneNodeAnimator(typeName, target); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorFactoryGetCreatableSceneNodeAnimatorTypeCount :: IO () %call %code int result = ISceneNodeAnimatorFactoryGetCreatableSceneNodeAnimatorTypeCount(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorFactoryGetCreateableSceneNodeAnimatorType :: Int -> IO () %call (int idx) %code int result = ISceneNodeAnimatorFactoryGetCreateableSceneNodeAnimatorType(idx); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorFactoryGetCreateableSceneNodeAnimatorTypeName :: Int -> IO () %call (int idx) %code int result = ISceneNodeAnimatorFactoryGetCreateableSceneNodeAnimatorTypeName(idx); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorFactoryGetCreateableSceneNodeAnimatorTypeName :: Int -> IO () %call (int type) %code int result = ISceneNodeAnimatorFactoryGetCreateableSceneNodeAnimatorTypeName(type); %fail {result < 0} {getError();} %fun IMeshSceneNodeIMeshSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int rotation) (int scale) (int parent) %code int result = IMeshSceneNodeIMeshSceneNode(parent, mgr, id, position, rotation, scale, parent); %fail {result < 0} {getError();} %fun IMeshSceneNodeSetMesh :: Int -> IO () %call (int mesh) %code int result = IMeshSceneNodeSetMesh(mesh); %fail {result < 0} {getError();} %fun IMeshSceneNodeGetMesh :: IO () %call %code int result = IMeshSceneNodeGetMesh(); %fail {result < 0} {getError();} %fun IMeshSceneNodeSetReadOnlyMaterials :: Int -> IO () %call (int readonly) %code int result = IMeshSceneNodeSetReadOnlyMaterials(readonly); %fail {result < 0} {getError();} %fun IMeshSceneNodeIsReadOnlyMaterials :: IO () %call %code int result = IMeshSceneNodeIsReadOnlyMaterials(); %fail {result < 0} {getError();} %fun ILoggerILogger :: IO () %call %code int result = ILoggerILogger(); %fail {result < 0} {getError();} %fun ILoggerGetLogLevel :: IO () %call %code int result = ILoggerGetLogLevel(); %fail {result < 0} {getError();} %fun ILoggerSetLogLevel :: Int -> IO () %call (int ll) %code int result = ILoggerSetLogLevel(ll); %fail {result < 0} {getError();} %fun ILoggerLog :: Int -> Int -> IO () %call (int text) (int ll) %code int result = ILoggerLog(text, ll); %fail {result < 0} {getError();} %fun ILoggerLog :: Int -> Int -> Int -> IO () %call (int text) (int hint) (int ll) %code int result = ILoggerLog(text, hint, ll); %fail {result < 0} {getError();} %fun ILoggerLog :: Int -> Int -> Int -> IO () %call (int text) (int hint) (int ll) %code int result = ILoggerLog(text, hint, ll); %fail {result < 0} {getError();} %fun ILoggerLog :: Int -> Int -> Int -> IO () %call (int text) (int hint) (int ll) %code int result = ILoggerLog(text, hint, ll); %fail {result < 0} {getError();} %fun ILoggerLog :: Int -> Int -> IO () %call (int text) (int ll) %code int result = ILoggerLog(text, ll); %fail {result < 0} {getError();} %fun IAnimatedMeshMD3SetInterpolationShift :: Int -> Int -> IO () %call (int shift) (int loopMode) %code int result = IAnimatedMeshMD3SetInterpolationShift(shift, loopMode); %fail {result < 0} {getError();} %fun IAnimatedMeshMD3GetTagList :: Int -> Int -> Int -> Int -> IO () %call (int frame) (int detailLevel) (int startFrameLoop) (int endFrameLoop) %code int result = IAnimatedMeshMD3GetTagList(frame, detailLevel, startFrameLoop, endFrameLoop); %fail {result < 0} {getError();} %fun IAnimatedMeshMD3GetOriginalMesh :: IO () %call %code int result = IAnimatedMeshMD3GetOriginalMesh(); %fail {result < 0} {getError();} %fun IReferenceCountedIReferenceCounted :: IO () %call %code int result = IReferenceCountedIReferenceCounted(); %fail {result < 0} {getError();} %fun IReferenceCountedIReferenceCounted :: IO () %call %code int result = IReferenceCountedIReferenceCounted(); %fail {result < 0} {getError();} %fun IReferenceCountedGrab :: IO () %call %code int result = IReferenceCountedGrab(); %fail {result < 0} {getError();} %fun IReferenceCountedDrop :: IO () %call %code int result = IReferenceCountedDrop(); %fail {result < 0} {getError();} %fun IReferenceCounted_IRR_DEBUG_BREAK_IF :: IO () %call %code int result = IReferenceCounted_IRR_DEBUG_BREAK_IF(); %fail {result < 0} {getError();} %fun IReferenceCountedGetReferenceCount :: IO () %call %code int result = IReferenceCountedGetReferenceCount(); %fail {result < 0} {getError();} %fun IReferenceCountedGetDebugName :: IO () %call %code int result = IReferenceCountedGetDebugName(); %fail {result < 0} {getError();} %fun IParticleMeshEmitterSetMesh :: Int -> IO () %call (int mesh) %code int result = IParticleMeshEmitterSetMesh(mesh); %fail {result < 0} {getError();} %fun IParticleMeshEmitterSetUseNormalDirection :: Int -> IO () %call (int useNormalDirection) %code int result = IParticleMeshEmitterSetUseNormalDirection(useNormalDirection); %fail {result < 0} {getError();} %fun IParticleMeshEmitterSetNormalDirectionModifier :: Int -> IO () %call (int normalDirectionModifier) %code int result = IParticleMeshEmitterSetNormalDirectionModifier(normalDirectionModifier); %fail {result < 0} {getError();} %fun IParticleMeshEmitterSetEveryMeshVertex :: Int -> IO () %call (int everyMeshVertex) %code int result = IParticleMeshEmitterSetEveryMeshVertex(everyMeshVertex); %fail {result < 0} {getError();} %fun IParticleMeshEmitterGetMesh :: IO () %call %code int result = IParticleMeshEmitterGetMesh(); %fail {result < 0} {getError();} %fun IParticleMeshEmitterIsUsingNormalDirection :: IO () %call %code int result = IParticleMeshEmitterIsUsingNormalDirection(); %fail {result < 0} {getError();} %fun IParticleMeshEmitterGetNormalDirectionModifier :: IO () %call %code int result = IParticleMeshEmitterGetNormalDirectionModifier(); %fail {result < 0} {getError();} %fun IParticleMeshEmitterGetEveryMeshVertex :: IO () %call %code int result = IParticleMeshEmitterGetEveryMeshVertex(); %fail {result < 0} {getError();} %fun IParticleMeshEmitterGetType :: IO () %call %code int result = IParticleMeshEmitterGetType(); %fail {result < 0} {getError();} %fun ICollisionCallbackOnCollision :: Int -> IO () %call (int animator) %code int result = ICollisionCallbackOnCollision(animator); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseISceneNodeAnimatorCollisionResponse :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseISceneNodeAnimatorCollisionResponse(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseIsFalling :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseIsFalling(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseSetEllipsoidRadius :: Int -> IO () %call (int radius) %code int result = ISceneNodeAnimatorCollisionResponseSetEllipsoidRadius(radius); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetEllipsoidRadius :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetEllipsoidRadius(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseSetGravity :: Int -> IO () %call (int gravity) %code int result = ISceneNodeAnimatorCollisionResponseSetGravity(gravity); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetGravity :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetGravity(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseJump :: Int -> IO () %call (int jumpSpeed) %code int result = ISceneNodeAnimatorCollisionResponseJump(jumpSpeed); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseSetAnimateTarget :: Int -> IO () %call (int enable) %code int result = ISceneNodeAnimatorCollisionResponseSetAnimateTarget(enable); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetAnimateTarget :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetAnimateTarget(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseSetEllipsoidTranslation :: Int -> IO () %call (int translation) %code int result = ISceneNodeAnimatorCollisionResponseSetEllipsoidTranslation(translation); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetEllipsoidTranslation :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetEllipsoidTranslation(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseSetWorld :: Int -> IO () %call (int newWorld) %code int result = ISceneNodeAnimatorCollisionResponseSetWorld(newWorld); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetWorld :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetWorld(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseSetTargetNode :: Int -> IO () %call (int node) %code int result = ISceneNodeAnimatorCollisionResponseSetTargetNode(node); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetTargetNode :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetTargetNode(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseCollisionOccurred :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseCollisionOccurred(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetCollisionPoint :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetCollisionPoint(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetCollisionTriangle :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetCollisionTriangle(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetCollisionResultPosition :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetCollisionResultPosition(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseGetCollisionNode :: IO () %call %code int result = ISceneNodeAnimatorCollisionResponseGetCollisionNode(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCollisionResponseSetCollisionCallback :: Int -> IO () %call (int callback) %code int result = ISceneNodeAnimatorCollisionResponseSetCollisionCallback(callback); %fail {result < 0} {getError();} %fun CDynamicMeshBufferCDynamicMeshBuffer :: Int -> Int -> IO () %call (int vertexType) (int indexType) %code int result = CDynamicMeshBufferCDynamicMeshBuffer(vertexType, indexType); %fail {result < 0} {getError();} %fun CDynamicMeshBufferCVertexBuffer :: IO () %call %code int result = CDynamicMeshBufferCVertexBuffer(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferCIndexBuffer :: IO () %call %code int result = CDynamicMeshBufferCIndexBuffer(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferCDynamicMeshBuffer :: IO () %call %code int result = CDynamicMeshBufferCDynamicMeshBuffer(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferGetVertexBuffer :: IO () %call %code int result = CDynamicMeshBufferGetVertexBuffer(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferGetIndexBuffer :: IO () %call %code int result = CDynamicMeshBufferGetIndexBuffer(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferSetVertexBuffer :: Int -> IO () %call (int newVertexBuffer) %code int result = CDynamicMeshBufferSetVertexBuffer(newVertexBuffer); %fail {result < 0} {getError();} %fun CDynamicMeshBufferSetIndexBuffer :: Int -> IO () %call (int newIndexBuffer) %code int result = CDynamicMeshBufferSetIndexBuffer(newIndexBuffer); %fail {result < 0} {getError();} %fun CDynamicMeshBufferGetMaterial :: IO () %call %code int result = CDynamicMeshBufferGetMaterial(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferGetMaterial :: IO () %call %code int result = CDynamicMeshBufferGetMaterial(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferGetBoundingBox :: IO () %call %code int result = CDynamicMeshBufferGetBoundingBox(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferSetBoundingBox :: Int -> IO () %call (int box) %code int result = CDynamicMeshBufferSetBoundingBox(box); %fail {result < 0} {getError();} %fun CDynamicMeshBufferRecalculateBoundingBox :: IO () %call %code int result = CDynamicMeshBufferRecalculateBoundingBox(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferReset :: Int -> IO () %call (int Pos) %code int result = CDynamicMeshBufferReset(Pos); %fail {result < 0} {getError();} %fun CDynamicMeshBufferGetVertexBuffer :: IO () %call %code int result = CDynamicMeshBufferGetVertexBuffer(); %fail {result < 0} {getError();} %fun CDynamicMeshBufferAddInternalPoint :: Int -> IO () %call (int Pos) %code int result = CDynamicMeshBufferAddInternalPoint(Pos); %fail {result < 0} {getError();} %fun IGUIFontBitmapGetType :: IO () %call %code int result = IGUIFontBitmapGetType(); %fail {result < 0} {getError();} %fun IGUIFontBitmapGetSpriteBank :: IO () %call %code int result = IGUIFontBitmapGetSpriteBank(); %fail {result < 0} {getError();} %fun IGUIFontBitmapGetSpriteNoFromChar :: Int -> IO () %call (int c) %code int result = IGUIFontBitmapGetSpriteNoFromChar(c); %fail {result < 0} {getError();} %fun IGUIFontBitmapGetKerningWidth :: Int -> Int -> IO () %call (int thisLetter) (int previousLetter) %code int result = IGUIFontBitmapGetKerningWidth(thisLetter, previousLetter); %fail {result < 0} {getError();} %fun IGUIInOutFaderIGUIInOutFader :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_IN_OUT_FADER) %code int result = IGUIInOutFaderIGUIInOutFader(environment, parent, id, EGUIET_IN_OUT_FADER); %fail {result < 0} {getError();} %fun IGUIInOutFaderGetColor :: IO () %call %code int result = IGUIInOutFaderGetColor(); %fail {result < 0} {getError();} %fun IGUIInOutFaderSetColor :: Int -> IO () %call (int color) %code int result = IGUIInOutFaderSetColor(color); %fail {result < 0} {getError();} %fun IGUIInOutFaderSetColor :: Int -> Int -> IO () %call (int source) (int dest) %code int result = IGUIInOutFaderSetColor(source, dest); %fail {result < 0} {getError();} %fun IGUIInOutFaderFadeIn :: Int -> IO () %call (int time) %code int result = IGUIInOutFaderFadeIn(time); %fail {result < 0} {getError();} %fun IGUIInOutFaderFadeOut :: Int -> IO () %call (int time) %code int result = IGUIInOutFaderFadeOut(time); %fail {result < 0} {getError();} %fun IGUIInOutFaderIsReady :: IO () %call %code int result = IGUIInOutFaderIsReady(); %fail {result < 0} {getError();} %fun IGUISpinBoxIGUISpinBox :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_SPIN_BOX) %code int result = IGUISpinBoxIGUISpinBox(environment, parent, id, EGUIET_SPIN_BOX); %fail {result < 0} {getError();} %fun IGUISpinBoxGetEditBox :: IO () %call %code int result = IGUISpinBoxGetEditBox(); %fail {result < 0} {getError();} %fun IGUISpinBoxSetValue :: Int -> IO () %call (int val) %code int result = IGUISpinBoxSetValue(val); %fail {result < 0} {getError();} %fun IGUISpinBoxGetValue :: IO () %call %code int result = IGUISpinBoxGetValue(); %fail {result < 0} {getError();} %fun IGUISpinBoxSetRange :: Int -> Int -> IO () %call (int min) (int max) %code int result = IGUISpinBoxSetRange(min, max); %fail {result < 0} {getError();} %fun IGUISpinBoxGetMin :: IO () %call %code int result = IGUISpinBoxGetMin(); %fail {result < 0} {getError();} %fun IGUISpinBoxGetMax :: IO () %call %code int result = IGUISpinBoxGetMax(); %fail {result < 0} {getError();} %fun IGUISpinBoxSetStepSize :: Int -> IO () %call (int step) %code int result = IGUISpinBoxSetStepSize(step); %fail {result < 0} {getError();} %fun IGUISpinBoxSetDecimalPlaces :: Int -> IO () %call (int places) %code int result = IGUISpinBoxSetDecimalPlaces(places); %fail {result < 0} {getError();} %fun IGUISpinBoxGetStepSize :: IO () %call %code int result = IGUISpinBoxGetStepSize(); %fail {result < 0} {getError();} %fun ICameraSceneNodeICameraSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int rotation) (int scale) (int parent) %code int result = ICameraSceneNodeICameraSceneNode(parent, mgr, id, position, rotation, scale, parent); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetProjectionMatrix :: Int -> Int -> IO () %call (int projection) (int isOrthogonal) %code int result = ICameraSceneNodeSetProjectionMatrix(projection, isOrthogonal); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetProjectionMatrix :: IO () %call %code int result = ICameraSceneNodeGetProjectionMatrix(); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetViewMatrix :: IO () %call %code int result = ICameraSceneNodeGetViewMatrix(); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetViewMatrixAffector :: Int -> IO () %call (int affector) %code int result = ICameraSceneNodeSetViewMatrixAffector(affector); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetViewMatrixAffector :: IO () %call %code int result = ICameraSceneNodeGetViewMatrixAffector(); %fail {result < 0} {getError();} %fun ICameraSceneNodeOnEvent :: Int -> IO () %call (int event) %code int result = ICameraSceneNodeOnEvent(event); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetTarget :: Int -> IO () %call (int pos) %code int result = ICameraSceneNodeSetTarget(pos); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetRotation :: Int -> IO () %call (int rotation) %code int result = ICameraSceneNodeSetRotation(rotation); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetTarget :: IO () %call %code int result = ICameraSceneNodeGetTarget(); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetUpVector :: Int -> IO () %call (int pos) %code int result = ICameraSceneNodeSetUpVector(pos); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetUpVector :: IO () %call %code int result = ICameraSceneNodeGetUpVector(); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetNearValue :: IO () %call %code int result = ICameraSceneNodeGetNearValue(); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetFarValue :: IO () %call %code int result = ICameraSceneNodeGetFarValue(); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetAspectRatio :: IO () %call %code int result = ICameraSceneNodeGetAspectRatio(); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetFOV :: IO () %call %code int result = ICameraSceneNodeGetFOV(); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetNearValue :: Int -> IO () %call (int zn) %code int result = ICameraSceneNodeSetNearValue(zn); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetFarValue :: Int -> IO () %call (int zf) %code int result = ICameraSceneNodeSetFarValue(zf); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetAspectRatio :: Int -> IO () %call (int aspect) %code int result = ICameraSceneNodeSetAspectRatio(aspect); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetFOV :: Int -> IO () %call (int fovy) %code int result = ICameraSceneNodeSetFOV(fovy); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetViewFrustum :: IO () %call %code int result = ICameraSceneNodeGetViewFrustum(); %fail {result < 0} {getError();} %fun ICameraSceneNodeSetInputReceiverEnabled :: Int -> IO () %call (int enabled) %code int result = ICameraSceneNodeSetInputReceiverEnabled(enabled); %fail {result < 0} {getError();} %fun ICameraSceneNodeIsInputReceiverEnabled :: IO () %call %code int result = ICameraSceneNodeIsInputReceiverEnabled(); %fail {result < 0} {getError();} %fun ICameraSceneNodeIsOrthogonal :: IO () %call %code int result = ICameraSceneNodeIsOrthogonal(); %fail {result < 0} {getError();} %fun ICameraSceneNodeBindTargetAndRotation :: Int -> IO () %call (int bound) %code int result = ICameraSceneNodeBindTargetAndRotation(bound); %fail {result < 0} {getError();} %fun ICameraSceneNodeGetTargetAndRotationBinding :: IO () %call %code int result = ICameraSceneNodeGetTargetAndRotationBinding(); %fail {result < 0} {getError();} %fun IParticleRingEmitterSetCenter :: Int -> IO () %call (int center) %code int result = IParticleRingEmitterSetCenter(center); %fail {result < 0} {getError();} %fun IParticleRingEmitterSetRadius :: Int -> IO () %call (int radius) %code int result = IParticleRingEmitterSetRadius(radius); %fail {result < 0} {getError();} %fun IParticleRingEmitterSetRingThickness :: Int -> IO () %call (int ringThickness) %code int result = IParticleRingEmitterSetRingThickness(ringThickness); %fail {result < 0} {getError();} %fun IParticleRingEmitterGetCenter :: IO () %call %code int result = IParticleRingEmitterGetCenter(); %fail {result < 0} {getError();} %fun IParticleRingEmitterGetRadius :: IO () %call %code int result = IParticleRingEmitterGetRadius(); %fail {result < 0} {getError();} %fun IParticleRingEmitterGetRingThickness :: IO () %call %code int result = IParticleRingEmitterGetRingThickness(); %fail {result < 0} {getError();} %fun IParticleRingEmitterGetType :: IO () %call %code int result = IParticleRingEmitterGetType(); %fail {result < 0} {getError();} %fun IParticleSphereEmitterSetCenter :: Int -> IO () %call (int center) %code int result = IParticleSphereEmitterSetCenter(center); %fail {result < 0} {getError();} %fun IParticleSphereEmitterSetRadius :: Int -> IO () %call (int radius) %code int result = IParticleSphereEmitterSetRadius(radius); %fail {result < 0} {getError();} %fun IParticleSphereEmitterGetCenter :: IO () %call %code int result = IParticleSphereEmitterGetCenter(); %fail {result < 0} {getError();} %fun IParticleSphereEmitterGetRadius :: IO () %call %code int result = IParticleSphereEmitterGetRadius(); %fail {result < 0} {getError();} %fun IParticleSphereEmitterGetType :: IO () %call %code int result = IParticleSphereEmitterGetType(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraMayaGetMoveSpeed :: IO () %call %code int result = ISceneNodeAnimatorCameraMayaGetMoveSpeed(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraMayaSetMoveSpeed :: Int -> IO () %call (int moveSpeed) %code int result = ISceneNodeAnimatorCameraMayaSetMoveSpeed(moveSpeed); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraMayaGetRotateSpeed :: IO () %call %code int result = ISceneNodeAnimatorCameraMayaGetRotateSpeed(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraMayaSetRotateSpeed :: Int -> IO () %call (int rotateSpeed) %code int result = ISceneNodeAnimatorCameraMayaSetRotateSpeed(rotateSpeed); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraMayaGetZoomSpeed :: IO () %call %code int result = ISceneNodeAnimatorCameraMayaGetZoomSpeed(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraMayaSetZoomSpeed :: Int -> IO () %call (int zoomSpeed) %code int result = ISceneNodeAnimatorCameraMayaSetZoomSpeed(zoomSpeed); %fail {result < 0} {getError();} %fun IParticleGravityAffectorSetTimeForceLost :: Int -> IO () %call (int timeForceLost) %code int result = IParticleGravityAffectorSetTimeForceLost(timeForceLost); %fail {result < 0} {getError();} %fun IParticleGravityAffectorSetGravity :: Int -> IO () %call (int gravity) %code int result = IParticleGravityAffectorSetGravity(gravity); %fail {result < 0} {getError();} %fun IParticleGravityAffectorGetTimeForceLost :: IO () %call %code int result = IParticleGravityAffectorGetTimeForceLost(); %fail {result < 0} {getError();} %fun IParticleGravityAffectorGetGravity :: IO () %call %code int result = IParticleGravityAffectorGetGravity(); %fail {result < 0} {getError();} %fun IParticleGravityAffectorGetType :: IO () %call %code int result = IParticleGravityAffectorGetType(); %fail {result < 0} {getError();} %fun ISceneNodeISceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int rotation) (int scale) %code int result = ISceneNodeISceneNode(parent, mgr, id, position, rotation, scale); %fail {result < 0} {getError();} %fun ISceneNodeUpdateAbsolutePosition :: IO () %call %code int result = ISceneNodeUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun ISceneNodeISceneNode :: IO () %call %code int result = ISceneNodeISceneNode(); %fail {result < 0} {getError();} %fun ISceneNodeRemoveAll :: IO () %call %code int result = ISceneNodeRemoveAll(); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeEnd :: IO () %call %code int result = ISceneNodeEnd(); %fail {result < 0} {getError();} %fun ISceneNodeOnRegisterSceneNode :: IO () %call %code int result = ISceneNodeOnRegisterSceneNode(); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeEnd :: IO () %call %code int result = ISceneNodeEnd(); %fail {result < 0} {getError();} %fun ISceneNodeOnAnimate :: Int -> IO () %call (int timeMs) %code int result = ISceneNodeOnAnimate(timeMs); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeWhile :: Int -> IO () %call (int ait) %code int result = ISceneNodeWhile(ait); %fail {result < 0} {getError();} %fun ISceneNodeAnimateNode :: IO () %call %code int result = ISceneNodeAnimateNode(); %fail {result < 0} {getError();} %fun ISceneNodeUpdateAbsolutePosition :: IO () %call %code int result = ISceneNodeUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeEnd :: IO () %call %code int result = ISceneNodeEnd(); %fail {result < 0} {getError();} %fun ISceneNodeRender :: IO () %call %code int result = ISceneNodeRender(); %fail {result < 0} {getError();} %fun ISceneNodeGetName :: IO () %call %code int result = ISceneNodeGetName(); %fail {result < 0} {getError();} %fun ISceneNodeSetName :: Int -> IO () %call (int name) %code int result = ISceneNodeSetName(name); %fail {result < 0} {getError();} %fun ISceneNodeSetName :: Int -> IO () %call (int name) %code int result = ISceneNodeSetName(name); %fail {result < 0} {getError();} %fun ISceneNodeGetBoundingBox :: IO () %call %code int result = ISceneNodeGetBoundingBox(); %fail {result < 0} {getError();} %fun ISceneNodeGetTransformedBoundingBox :: IO () %call %code int result = ISceneNodeGetTransformedBoundingBox(); %fail {result < 0} {getError();} %fun ISceneNodeGetBoundingBox :: IO () %call %code int result = ISceneNodeGetBoundingBox(); %fail {result < 0} {getError();} %fun ISceneNodeTransformBoxEx :: IO () %call %code int result = ISceneNodeTransformBoxEx(); %fail {result < 0} {getError();} %fun ISceneNodeGetAbsoluteTransformation :: IO () %call %code int result = ISceneNodeGetAbsoluteTransformation(); %fail {result < 0} {getError();} %fun ISceneNodeGetRelativeTransformation :: IO () %call %code int result = ISceneNodeGetRelativeTransformation(); %fail {result < 0} {getError();} %fun ISceneNodeSetRotationDegrees :: IO () %call %code int result = ISceneNodeSetRotationDegrees(); %fail {result < 0} {getError();} %fun ISceneNodeSetTranslation :: IO () %call %code int result = ISceneNodeSetTranslation(); %fail {result < 0} {getError();} %fun ISceneNodeSetScale :: IO () %call %code int result = ISceneNodeSetScale(); %fail {result < 0} {getError();} %fun ISceneNodeIsVisible :: IO () %call %code int result = ISceneNodeIsVisible(); %fail {result < 0} {getError();} %fun ISceneNodeIsTrulyVisible :: IO () %call %code int result = ISceneNodeIsTrulyVisible(); %fail {result < 0} {getError();} %fun ISceneNodeSetVisible :: Int -> IO () %call (int isVisible) %code int result = ISceneNodeSetVisible(isVisible); %fail {result < 0} {getError();} %fun ISceneNodeGetID :: IO () %call %code int result = ISceneNodeGetID(); %fail {result < 0} {getError();} %fun ISceneNodeSetID :: Int -> IO () %call (int id) %code int result = ISceneNodeSetID(id); %fail {result < 0} {getError();} %fun ISceneNodeAddChild :: Int -> IO () %call (int child) %code int result = ISceneNodeAddChild(child); %fail {result < 0} {getError();} %fun ISceneNodeGrab :: IO () %call %code int result = ISceneNodeGrab(); %fail {result < 0} {getError();} %fun ISceneNodeRemove :: IO () %call %code int result = ISceneNodeRemove(); %fail {result < 0} {getError();} %fun ISceneNodePush_back :: IO () %call %code int result = ISceneNodePush_back(); %fail {result < 0} {getError();} %fun ISceneNodeRemoveChild :: Int -> IO () %call (int child) %code int result = ISceneNodeRemoveChild(child); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeEnd :: IO () %call %code int result = ISceneNodeEnd(); %fail {result < 0} {getError();} %fun ISceneNodeErase :: IO () %call %code int result = ISceneNodeErase(); %fail {result < 0} {getError();} %fun ISceneNodeRemoveAll :: IO () %call %code int result = ISceneNodeRemoveAll(); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeEnd :: IO () %call %code int result = ISceneNodeEnd(); %fail {result < 0} {getError();} %fun ISceneNodeClear :: IO () %call %code int result = ISceneNodeClear(); %fail {result < 0} {getError();} %fun ISceneNodeRemove :: IO () %call %code int result = ISceneNodeRemove(); %fail {result < 0} {getError();} %fun ISceneNodeAddAnimator :: Int -> IO () %call (int animator) %code int result = ISceneNodeAddAnimator(animator); %fail {result < 0} {getError();} %fun ISceneNodePush_back :: IO () %call %code int result = ISceneNodePush_back(); %fail {result < 0} {getError();} %fun ISceneNodeGrab :: IO () %call %code int result = ISceneNodeGrab(); %fail {result < 0} {getError();} %fun ISceneNodeGetAnimators :: IO () %call %code int result = ISceneNodeGetAnimators(); %fail {result < 0} {getError();} %fun ISceneNodeRemoveAnimator :: Int -> IO () %call (int animator) %code int result = ISceneNodeRemoveAnimator(animator); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeEnd :: IO () %call %code int result = ISceneNodeEnd(); %fail {result < 0} {getError();} %fun ISceneNodeErase :: IO () %call %code int result = ISceneNodeErase(); %fail {result < 0} {getError();} %fun ISceneNodeRemoveAnimators :: IO () %call %code int result = ISceneNodeRemoveAnimators(); %fail {result < 0} {getError();} %fun ISceneNodeBegin :: IO () %call %code int result = ISceneNodeBegin(); %fail {result < 0} {getError();} %fun ISceneNodeEnd :: IO () %call %code int result = ISceneNodeEnd(); %fail {result < 0} {getError();} %fun ISceneNodeClear :: IO () %call %code int result = ISceneNodeClear(); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterial :: Int -> IO () %call (int num) %code int result = ISceneNodeGetMaterial(num); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterialCount :: IO () %call %code int result = ISceneNodeGetMaterialCount(); %fail {result < 0} {getError();} %fun ISceneNodeSetMaterialFlag :: Int -> Int -> IO () %call (int flag) (int newvalue) %code int result = ISceneNodeSetMaterialFlag(flag, newvalue); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterialCount :: IO () %call %code int result = ISceneNodeGetMaterialCount(); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterial :: Int -> IO () %call (int flag) %code int result = ISceneNodeGetMaterial(flag); %fail {result < 0} {getError();} %fun ISceneNodeSetMaterialTexture :: Int -> Int -> IO () %call (int textureLayer) (int texture) %code int result = ISceneNodeSetMaterialTexture(textureLayer, texture); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterialCount :: IO () %call %code int result = ISceneNodeGetMaterialCount(); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterial :: Int -> IO () %call (int textureLayer) %code int result = ISceneNodeGetMaterial(textureLayer); %fail {result < 0} {getError();} %fun ISceneNodeSetMaterialType :: Int -> IO () %call (int newType) %code int result = ISceneNodeSetMaterialType(newType); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterialCount :: IO () %call %code int result = ISceneNodeGetMaterialCount(); %fail {result < 0} {getError();} %fun ISceneNodeGetMaterial :: IO () %call %code int result = ISceneNodeGetMaterial(); %fail {result < 0} {getError();} %fun ISceneNodeGetScale :: IO () %call %code int result = ISceneNodeGetScale(); %fail {result < 0} {getError();} %fun ISceneNodeSetScale :: Int -> IO () %call (int scale) %code int result = ISceneNodeSetScale(scale); %fail {result < 0} {getError();} %fun ISceneNodeGetRotation :: IO () %call %code int result = ISceneNodeGetRotation(); %fail {result < 0} {getError();} %fun ISceneNodeSetRotation :: Int -> IO () %call (int rotation) %code int result = ISceneNodeSetRotation(rotation); %fail {result < 0} {getError();} %fun ISceneNodeGetPosition :: IO () %call %code int result = ISceneNodeGetPosition(); %fail {result < 0} {getError();} %fun ISceneNodeSetPosition :: Int -> IO () %call (int newpos) %code int result = ISceneNodeSetPosition(newpos); %fail {result < 0} {getError();} %fun ISceneNodeGetAbsolutePosition :: IO () %call %code int result = ISceneNodeGetAbsolutePosition(); %fail {result < 0} {getError();} %fun ISceneNodeSetAutomaticCulling :: Int -> IO () %call (int state) %code int result = ISceneNodeSetAutomaticCulling(state); %fail {result < 0} {getError();} %fun ISceneNodeGetAutomaticCulling :: IO () %call %code int result = ISceneNodeGetAutomaticCulling(); %fail {result < 0} {getError();} %fun ISceneNodeSetDebugDataVisible :: Int -> IO () %call (int state) %code int result = ISceneNodeSetDebugDataVisible(state); %fail {result < 0} {getError();} %fun ISceneNodeIsDebugDataVisible :: IO () %call %code int result = ISceneNodeIsDebugDataVisible(); %fail {result < 0} {getError();} %fun ISceneNodeSetIsDebugObject :: Int -> IO () %call (int debugObject) %code int result = ISceneNodeSetIsDebugObject(debugObject); %fail {result < 0} {getError();} %fun ISceneNodeIsDebugObject :: IO () %call %code int result = ISceneNodeIsDebugObject(); %fail {result < 0} {getError();} %fun ISceneNodeGetChildren :: IO () %call %code int result = ISceneNodeGetChildren(); %fail {result < 0} {getError();} %fun ISceneNodeSetParent :: Int -> IO () %call (int newParent) %code int result = ISceneNodeSetParent(newParent); %fail {result < 0} {getError();} %fun ISceneNodeGrab :: IO () %call %code int result = ISceneNodeGrab(); %fail {result < 0} {getError();} %fun ISceneNodeRemove :: IO () %call %code int result = ISceneNodeRemove(); %fail {result < 0} {getError();} %fun ISceneNodeDrop :: IO () %call %code int result = ISceneNodeDrop(); %fail {result < 0} {getError();} %fun ISceneNodeGetTriangleSelector :: IO () %call %code int result = ISceneNodeGetTriangleSelector(); %fail {result < 0} {getError();} %fun ISceneNodeSetTriangleSelector :: Int -> IO () %call (int selector) %code int result = ISceneNodeSetTriangleSelector(selector); %fail {result < 0} {getError();} %fun ISceneNodeUpdateAbsolutePosition :: IO () %call %code int result = ISceneNodeUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun ISceneNodeGetAbsoluteTransformation :: IO () %call %code int result = ISceneNodeGetAbsoluteTransformation(); %fail {result < 0} {getError();} %fun ISceneNodeGetRelativeTransformation :: IO () %call %code int result = ISceneNodeGetRelativeTransformation(); %fail {result < 0} {getError();} %fun ISceneNodeGetParent :: IO () %call %code int result = ISceneNodeGetParent(); %fail {result < 0} {getError();} %fun ISceneNodeGetType :: IO () %call %code int result = ISceneNodeGetType(); %fail {result < 0} {getError();} %fun ISceneNodeSerializeAttributes :: Int -> Int -> IO () %call (int out) (int options) %code int result = ISceneNodeSerializeAttributes(out, options); %fail {result < 0} {getError();} %fun ISceneNodeAddString :: IO () %call %code int result = ISceneNodeAddString(); %fail {result < 0} {getError();} %fun ISceneNodeAddInt :: IO () %call %code int result = ISceneNodeAddInt(); %fail {result < 0} {getError();} %fun ISceneNodeAddVector3d :: IO () %call %code int result = ISceneNodeAddVector3d(); %fail {result < 0} {getError();} %fun ISceneNodeAddVector3d :: IO () %call %code int result = ISceneNodeAddVector3d(); %fail {result < 0} {getError();} %fun ISceneNodeAddVector3d :: IO () %call %code int result = ISceneNodeAddVector3d(); %fail {result < 0} {getError();} %fun ISceneNodeAddBool :: IO () %call %code int result = ISceneNodeAddBool(); %fail {result < 0} {getError();} %fun ISceneNodeAddInt :: IO () %call %code int result = ISceneNodeAddInt(); %fail {result < 0} {getError();} %fun ISceneNodeAddInt :: IO () %call %code int result = ISceneNodeAddInt(); %fail {result < 0} {getError();} %fun ISceneNodeAddBool :: IO () %call %code int result = ISceneNodeAddBool(); %fail {result < 0} {getError();} %fun ISceneNodeDeserializeAttributes :: Int -> Int -> IO () %call (int i_n) (int options) %code int result = ISceneNodeDeserializeAttributes(i_n, options); %fail {result < 0} {getError();} %fun ISceneNodeGetAttributeAsString :: IO () %call %code int result = ISceneNodeGetAttributeAsString(); %fail {result < 0} {getError();} %fun ISceneNodeGetAttributeAsInt :: IO () %call %code int result = ISceneNodeGetAttributeAsInt(); %fail {result < 0} {getError();} %fun ISceneNodeSetPosition :: IO () %call %code int result = ISceneNodeSetPosition(); %fail {result < 0} {getError();} %fun ISceneNodeSetRotation :: IO () %call %code int result = ISceneNodeSetRotation(); %fail {result < 0} {getError();} %fun ISceneNodeSetScale :: IO () %call %code int result = ISceneNodeSetScale(); %fail {result < 0} {getError();} %fun ISceneNodeGetAttributeAsBool :: IO () %call %code int result = ISceneNodeGetAttributeAsBool(); %fail {result < 0} {getError();} %fun ISceneNodeGetAttributeAsEnumeration :: Int -> IO () %call (int AutomaticCullingNames) %code int result = ISceneNodeGetAttributeAsEnumeration(AutomaticCullingNames); %fail {result < 0} {getError();} %fun ISceneNodeGetAttributeAsInt :: IO () %call %code int result = ISceneNodeGetAttributeAsInt(); %fail {result < 0} {getError();} %fun ISceneNodeGetAttributeAsInt :: IO () %call %code int result = ISceneNodeGetAttributeAsInt(); %fail {result < 0} {getError();} %fun ISceneNodeGetAttributeAsBool :: IO () %call %code int result = ISceneNodeGetAttributeAsBool(); %fail {result < 0} {getError();} %fun ISceneNodeUpdateAbsolutePosition :: IO () %call %code int result = ISceneNodeUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun ISceneNodeClone :: Int -> Int -> IO () %call (int newParent) (int newManager) %code int result = ISceneNodeClone(newParent, newManager); %fail {result < 0} {getError();} %fun ISceneNodeGetSceneManager :: IO () %call %code int result = ISceneNodeGetSceneManager(); %fail {result < 0} {getError();} %fun ITextSceneNodeITextSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int parent) %code int result = ITextSceneNodeITextSceneNode(parent, mgr, id, position, parent); %fail {result < 0} {getError();} %fun ITextSceneNodeSetText :: Int -> IO () %call (int text) %code int result = ITextSceneNodeSetText(text); %fail {result < 0} {getError();} %fun ITextSceneNodeSetTextColor :: Int -> IO () %call (int color) %code int result = ITextSceneNodeSetTextColor(color); %fail {result < 0} {getError();} %fun SMaterialLayerSMaterialLayer :: IO () %call %code int result = SMaterialLayerSMaterialLayer(); %fail {result < 0} {getError();} %fun SMaterialLayerSMaterialLayer :: Int -> IO () %call (int other) %code int result = SMaterialLayerSMaterialLayer(other); %fail {result < 0} {getError();} %fun SMaterialLayerSMaterialLayer :: IO () %call %code int result = SMaterialLayerSMaterialLayer(); %fail {result < 0} {getError();} %fun SMaterialLayerDestruct :: IO () %call %code int result = SMaterialLayerDestruct(); %fail {result < 0} {getError();} %fun SMaterialLayerDeallocate :: IO () %call %code int result = SMaterialLayerDeallocate(); %fail {result < 0} {getError();} %fun SMaterialLayerDestruct :: IO () %call %code int result = SMaterialLayerDestruct(); %fail {result < 0} {getError();} %fun SMaterialLayerDeallocate :: IO () %call %code int result = SMaterialLayerDeallocate(); %fail {result < 0} {getError();} %fun SMaterialLayerAllocate :: IO () %call %code int result = SMaterialLayerAllocate(); %fail {result < 0} {getError();} %fun SMaterialLayerConstruct :: Int -> IO () %call (int TextureMatrix) %code int result = SMaterialLayerConstruct(TextureMatrix); %fail {result < 0} {getError();} %fun SMaterialLayerGetTextureMatrix :: IO () %call %code int result = SMaterialLayerGetTextureMatrix(); %fail {result < 0} {getError();} %fun SMaterialLayerAllocate :: IO () %call %code int result = SMaterialLayerAllocate(); %fail {result < 0} {getError();} %fun SMaterialLayerConstruct :: Int -> IO () %call (int IdentityMatrix) %code int result = SMaterialLayerConstruct(IdentityMatrix); %fail {result < 0} {getError();} %fun SMaterialLayerGetTextureMatrix :: IO () %call %code int result = SMaterialLayerGetTextureMatrix(); %fail {result < 0} {getError();} %fun SMaterialLayerSetTextureMatrix :: Int -> IO () %call (int mat) %code int result = SMaterialLayerSetTextureMatrix(mat); %fail {result < 0} {getError();} %fun SMaterialLayerAllocate :: IO () %call %code int result = SMaterialLayerAllocate(); %fail {result < 0} {getError();} %fun SMaterialLayerConstruct :: IO () %call %code int result = SMaterialLayerConstruct(); %fail {result < 0} {getError();} %fun IGUIStaticTextIGUIStaticText :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_STATIC_TEXT) %code int result = IGUIStaticTextIGUIStaticText(environment, parent, id, EGUIET_STATIC_TEXT); %fail {result < 0} {getError();} %fun IGUIStaticTextSetOverrideFont :: Int -> IO () %call (int font) %code int result = IGUIStaticTextSetOverrideFont(font); %fail {result < 0} {getError();} %fun IGUIStaticTextGetOverrideFont :: IO () %call %code int result = IGUIStaticTextGetOverrideFont(); %fail {result < 0} {getError();} %fun IGUIStaticTextSetOverrideColor :: Int -> IO () %call (int color) %code int result = IGUIStaticTextSetOverrideColor(color); %fail {result < 0} {getError();} %fun IGUIStaticTextGetOverrideColor :: IO () %call %code int result = IGUIStaticTextGetOverrideColor(); %fail {result < 0} {getError();} %fun IGUIStaticTextEnableOverrideColor :: Int -> IO () %call (int enable) %code int result = IGUIStaticTextEnableOverrideColor(enable); %fail {result < 0} {getError();} %fun IGUIStaticTextIsOverrideColorEnabled :: IO () %call %code int result = IGUIStaticTextIsOverrideColorEnabled(); %fail {result < 0} {getError();} %fun IGUIStaticTextSetBackgroundColor :: Int -> IO () %call (int color) %code int result = IGUIStaticTextSetBackgroundColor(color); %fail {result < 0} {getError();} %fun IGUIStaticTextSetDrawBackground :: Int -> IO () %call (int draw) %code int result = IGUIStaticTextSetDrawBackground(draw); %fail {result < 0} {getError();} %fun IGUIStaticTextSetDrawBorder :: Int -> IO () %call (int draw) %code int result = IGUIStaticTextSetDrawBorder(draw); %fail {result < 0} {getError();} %fun IGUIStaticTextSetTextAlignment :: Int -> Int -> IO () %call (int horizontal) (int vertical) %code int result = IGUIStaticTextSetTextAlignment(horizontal, vertical); %fail {result < 0} {getError();} %fun IGUIStaticTextSetWordWrap :: Int -> IO () %call (int enable) %code int result = IGUIStaticTextSetWordWrap(enable); %fail {result < 0} {getError();} %fun IGUIStaticTextIsWordWrapEnabled :: IO () %call %code int result = IGUIStaticTextIsWordWrapEnabled(); %fail {result < 0} {getError();} %fun IGUIStaticTextGetTextHeight :: IO () %call %code int result = IGUIStaticTextGetTextHeight(); %fail {result < 0} {getError();} %fun IGUIStaticTextGetTextWidth :: IO () %call %code int result = IGUIStaticTextGetTextWidth(); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeIParticleSystemSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int rotation) (int scale) (int parent) %code int result = IParticleSystemSceneNodeIParticleSystemSceneNode(parent, mgr, id, position, rotation, scale, parent); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeSetParticleSize :: Int -> IO () %call (int size) %code int result = IParticleSystemSceneNodeSetParticleSize(size); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeSetParticlesAreGlobal :: Int -> IO () %call (int global) %code int result = IParticleSystemSceneNodeSetParticlesAreGlobal(global); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeGetEmitter :: IO () %call %code int result = IParticleSystemSceneNodeGetEmitter(); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeSetEmitter :: Int -> IO () %call (int emitter) %code int result = IParticleSystemSceneNodeSetEmitter(emitter); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeAddAffector :: Int -> IO () %call (int affector) %code int result = IParticleSystemSceneNodeAddAffector(affector); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeRemoveAllAffectors :: IO () %call %code int result = IParticleSystemSceneNodeRemoveAllAffectors(); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateAnimatedMeshSceneNodeEmitter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int node) (int useNormalDirection) (int direction) (int normalDirectionModifier) (int mbNumber) (int everyMeshVertex) (int minParticlesPerSecond) (int maxParticlesPerSecond) (int minStartColor) (int maxStartColor) (int lifeTimeMin) (int lifeTimeMax) (int maxAngleDegrees) (int minStartSize) (int maxStartSize) %code int result = IParticleSystemSceneNodeCreateAnimatedMeshSceneNodeEmitter(node, useNormalDirection, direction, normalDirectionModifier, mbNumber, everyMeshVertex, minParticlesPerSecond, maxParticlesPerSecond, minStartColor, maxStartColor, lifeTimeMin, lifeTimeMax, maxAngleDegrees, minStartSize, maxStartSize); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateBoxEmitter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int box) (int direction) (int minParticlesPerSecond) (int maxParticlesPerSecond) (int minStartColor) (int maxStartColor) (int lifeTimeMin) (int lifeTimeMax) (int maxAngleDegrees) (int minStartSize) (int maxStartSize) %code int result = IParticleSystemSceneNodeCreateBoxEmitter(box, direction, minParticlesPerSecond, maxParticlesPerSecond, minStartColor, maxStartColor, lifeTimeMin, lifeTimeMax, maxAngleDegrees, minStartSize, maxStartSize); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateCylinderEmitter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int center) (int radius) (int normal) (int length) (int outlineOnly) (int direction) (int minParticlesPerSecond) (int maxParticlesPerSecond) (int minStartColor) (int maxStartColor) (int lifeTimeMin) (int lifeTimeMax) (int maxAngleDegrees) (int minStartSize) (int maxStartSize) %code int result = IParticleSystemSceneNodeCreateCylinderEmitter(center, radius, normal, length, outlineOnly, direction, minParticlesPerSecond, maxParticlesPerSecond, minStartColor, maxStartColor, lifeTimeMin, lifeTimeMax, maxAngleDegrees, minStartSize, maxStartSize); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateMeshEmitter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int useNormalDirection) (int direction) (int normalDirectionModifier) (int mbNumber) (int everyMeshVertex) (int minParticlesPerSecond) (int maxParticlesPerSecond) (int minStartColor) (int maxStartColor) (int lifeTimeMin) (int lifeTimeMax) (int maxAngleDegrees) (int minStartSize) (int maxStartSize) %code int result = IParticleSystemSceneNodeCreateMeshEmitter(mesh, useNormalDirection, direction, normalDirectionModifier, mbNumber, everyMeshVertex, minParticlesPerSecond, maxParticlesPerSecond, minStartColor, maxStartColor, lifeTimeMin, lifeTimeMax, maxAngleDegrees, minStartSize, maxStartSize); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreatePointEmitter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int direction) (int minParticlesPerSecond) (int maxParticlesPerSecond) (int minStartColor) (int maxStartColor) (int lifeTimeMin) (int lifeTimeMax) (int maxAngleDegrees) (int minStartSize) (int maxStartSize) %code int result = IParticleSystemSceneNodeCreatePointEmitter(direction, minParticlesPerSecond, maxParticlesPerSecond, minStartColor, maxStartColor, lifeTimeMin, lifeTimeMax, maxAngleDegrees, minStartSize, maxStartSize); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateRingEmitter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int center) (int radius) (int ringThickness) (int direction) (int minParticlesPerSecond) (int maxParticlesPerSecond) (int minStartColor) (int maxStartColor) (int lifeTimeMin) (int lifeTimeMax) (int maxAngleDegrees) (int minStartSize) (int maxStartSize) %code int result = IParticleSystemSceneNodeCreateRingEmitter(center, radius, ringThickness, direction, minParticlesPerSecond, maxParticlesPerSecond, minStartColor, maxStartColor, lifeTimeMin, lifeTimeMax, maxAngleDegrees, minStartSize, maxStartSize); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateSphereEmitter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int center) (int radius) (int direction) (int minParticlesPerSecond) (int maxParticlesPerSecond) (int minStartColor) (int maxStartColor) (int lifeTimeMin) (int lifeTimeMax) (int maxAngleDegrees) (int minStartSize) (int maxStartSize) %code int result = IParticleSystemSceneNodeCreateSphereEmitter(center, radius, direction, minParticlesPerSecond, maxParticlesPerSecond, minStartColor, maxStartColor, lifeTimeMin, lifeTimeMax, maxAngleDegrees, minStartSize, maxStartSize); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateAttractionAffector :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int point) (int speed) (int attract) (int affectX) (int affectY) (int affectZ) %code int result = IParticleSystemSceneNodeCreateAttractionAffector(point, speed, attract, affectX, affectY, affectZ); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateScaleParticleAffector :: Int -> IO () %call (int scaleTo) %code int result = IParticleSystemSceneNodeCreateScaleParticleAffector(scaleTo); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateFadeOutParticleAffector :: Int -> Int -> IO () %call (int targetColor) (int timeNeededToFadeOut) %code int result = IParticleSystemSceneNodeCreateFadeOutParticleAffector(targetColor, timeNeededToFadeOut); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateGravityAffector :: Int -> Int -> IO () %call (int gravity) (int timeForceLost) %code int result = IParticleSystemSceneNodeCreateGravityAffector(gravity, timeForceLost); %fail {result < 0} {getError();} %fun IParticleSystemSceneNodeCreateRotationAffector :: Int -> Int -> IO () %call (int speed) (int pivotPoint) %code int result = IParticleSystemSceneNodeCreateRotationAffector(speed, pivotPoint); %fail {result < 0} {getError();} %fun ITerrainSceneNodeITerrainSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int rotation) (int scale) (int parent) %code int result = ITerrainSceneNodeITerrainSceneNode(parent, mgr, id, position, rotation, scale, parent); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetBoundingBox :: IO () %call %code int result = ITerrainSceneNodeGetBoundingBox(); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetBoundingBox :: Int -> Int -> IO () %call (int patchX) (int patchZ) %code int result = ITerrainSceneNodeGetBoundingBox(patchX, patchZ); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetIndexCount :: IO () %call %code int result = ITerrainSceneNodeGetIndexCount(); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetMesh :: IO () %call %code int result = ITerrainSceneNodeGetMesh(); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetRenderBuffer :: IO () %call %code int result = ITerrainSceneNodeGetRenderBuffer(); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetMeshBufferForLOD :: Int -> Int -> IO () %call (int mb) (int LOD) %code int result = ITerrainSceneNodeGetMeshBufferForLOD(mb, LOD); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetIndicesForPatch :: Int -> Int -> Int -> Int -> IO () %call (int indices) (int patchX) (int patchZ) (int LOD) %code int result = ITerrainSceneNodeGetIndicesForPatch(indices, patchX, patchZ, LOD); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetCurrentLODOfPatches :: Int -> IO () %call (int LODs) %code int result = ITerrainSceneNodeGetCurrentLODOfPatches(LODs); %fail {result < 0} {getError();} %fun ITerrainSceneNodeSetLODOfPatch :: Int -> Int -> Int -> IO () %call (int patchX) (int patchZ) (int LOD) %code int result = ITerrainSceneNodeSetLODOfPatch(patchX, patchZ, LOD); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetTerrainCenter :: IO () %call %code int result = ITerrainSceneNodeGetTerrainCenter(); %fail {result < 0} {getError();} %fun ITerrainSceneNodeGetHeight :: Int -> Int -> IO () %call (int x) (int y) %code int result = ITerrainSceneNodeGetHeight(x, y); %fail {result < 0} {getError();} %fun ITerrainSceneNodeSetCameraMovementDelta :: Int -> IO () %call (int delta) %code int result = ITerrainSceneNodeSetCameraMovementDelta(delta); %fail {result < 0} {getError();} %fun ITerrainSceneNodeSetCameraRotationDelta :: Int -> IO () %call (int delta) %code int result = ITerrainSceneNodeSetCameraRotationDelta(delta); %fail {result < 0} {getError();} %fun ITerrainSceneNodeSetDynamicSelectorUpdate :: Int -> IO () %call (int bVal) %code int result = ITerrainSceneNodeSetDynamicSelectorUpdate(bVal); %fail {result < 0} {getError();} %fun ITerrainSceneNodeOverrideLODDistance :: Int -> Int -> IO () %call (int LOD) (int newDistance) %code int result = ITerrainSceneNodeOverrideLODDistance(LOD, newDistance); %fail {result < 0} {getError();} %fun ITerrainSceneNodeScaleTexture :: Int -> Int -> IO () %call (int scale) (int scale2) %code int result = ITerrainSceneNodeScaleTexture(scale, scale2); %fail {result < 0} {getError();} %fun ITerrainSceneNodeLoadHeightMap :: Int -> Int -> Int -> IO () %call (int file) (int vertexColor) (int smoothFactor) %code int result = ITerrainSceneNodeLoadHeightMap(file, vertexColor, smoothFactor); %fail {result < 0} {getError();} %fun ITerrainSceneNodeLoadHeightMapRAW :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int file) (int bitsPerPixel) (int signedData) (int floatVals) (int width) (int vertexColor) (int smoothFactor) %code int result = ITerrainSceneNodeLoadHeightMapRAW(file, bitsPerPixel, signedData, floatVals, width, vertexColor, smoothFactor); %fail {result < 0} {getError();} %fun IGUIContextMenuIGUIContextMenu :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_CONTEXT_MENU) %code int result = IGUIContextMenuIGUIContextMenu(environment, parent, id, EGUIET_CONTEXT_MENU); %fail {result < 0} {getError();} %fun IGUIContextMenuSetCloseHandling :: Int -> IO () %call (int onClose) %code int result = IGUIContextMenuSetCloseHandling(onClose); %fail {result < 0} {getError();} %fun IGUIContextMenuGetCloseHandling :: IO () %call %code int result = IGUIContextMenuGetCloseHandling(); %fail {result < 0} {getError();} %fun IGUIContextMenuGetItemCount :: IO () %call %code int result = IGUIContextMenuGetItemCount(); %fail {result < 0} {getError();} %fun IGUIContextMenuAddItem :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int text) (int commandId) (int enabled) (int hasSubMenu) (int checked) (int autoChecking) %code int result = IGUIContextMenuAddItem(text, commandId, enabled, hasSubMenu, checked, autoChecking); %fail {result < 0} {getError();} %fun IGUIContextMenuInsertItem :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int idx) (int text) (int commandId) (int enabled) (int hasSubMenu) (int checked) (int autoChecking) %code int result = IGUIContextMenuInsertItem(idx, text, commandId, enabled, hasSubMenu, checked, autoChecking); %fail {result < 0} {getError();} %fun IGUIContextMenuFindItemWithCommandId :: Int -> Int -> IO () %call (int commandId) (int idxStartSearch) %code int result = IGUIContextMenuFindItemWithCommandId(commandId, idxStartSearch); %fail {result < 0} {getError();} %fun IGUIContextMenuAddSeparator :: IO () %call %code int result = IGUIContextMenuAddSeparator(); %fail {result < 0} {getError();} %fun IGUIContextMenuGetItemText :: Int -> IO () %call (int idx) %code int result = IGUIContextMenuGetItemText(idx); %fail {result < 0} {getError();} %fun IGUIContextMenuSetItemText :: Int -> Int -> IO () %call (int idx) (int text) %code int result = IGUIContextMenuSetItemText(idx, text); %fail {result < 0} {getError();} %fun IGUIContextMenuIsItemEnabled :: Int -> IO () %call (int idx) %code int result = IGUIContextMenuIsItemEnabled(idx); %fail {result < 0} {getError();} %fun IGUIContextMenuSetItemEnabled :: Int -> Int -> IO () %call (int idx) (int enabled) %code int result = IGUIContextMenuSetItemEnabled(idx, enabled); %fail {result < 0} {getError();} %fun IGUIContextMenuSetItemChecked :: Int -> Int -> IO () %call (int idx) (int enabled) %code int result = IGUIContextMenuSetItemChecked(idx, enabled); %fail {result < 0} {getError();} %fun IGUIContextMenuIsItemChecked :: Int -> IO () %call (int idx) %code int result = IGUIContextMenuIsItemChecked(idx); %fail {result < 0} {getError();} %fun IGUIContextMenuRemoveItem :: Int -> IO () %call (int idx) %code int result = IGUIContextMenuRemoveItem(idx); %fail {result < 0} {getError();} %fun IGUIContextMenuRemoveAllItems :: IO () %call %code int result = IGUIContextMenuRemoveAllItems(); %fail {result < 0} {getError();} %fun IGUIContextMenuGetSelectedItem :: IO () %call %code int result = IGUIContextMenuGetSelectedItem(); %fail {result < 0} {getError();} %fun IGUIContextMenuGetItemCommandId :: Int -> IO () %call (int idx) %code int result = IGUIContextMenuGetItemCommandId(idx); %fail {result < 0} {getError();} %fun IGUIContextMenuSetItemCommandId :: Int -> Int -> IO () %call (int idx) (int id) %code int result = IGUIContextMenuSetItemCommandId(idx, id); %fail {result < 0} {getError();} %fun IGUIContextMenuGetSubMenu :: Int -> IO () %call (int idx) %code int result = IGUIContextMenuGetSubMenu(idx); %fail {result < 0} {getError();} %fun IGUIContextMenuSetItemAutoChecking :: Int -> Int -> IO () %call (int idx) (int autoChecking) %code int result = IGUIContextMenuSetItemAutoChecking(idx, autoChecking); %fail {result < 0} {getError();} %fun IGUIContextMenuGetItemAutoChecking :: Int -> IO () %call (int idx) %code int result = IGUIContextMenuGetItemAutoChecking(idx); %fail {result < 0} {getError();} %fun IGUIContextMenuSetEventParent :: Int -> IO () %call (int parent) %code int result = IGUIContextMenuSetEventParent(parent); %fail {result < 0} {getError();} %fun IImageLock :: IO () %call %code int result = IImageLock(); %fail {result < 0} {getError();} %fun IImageUnlock :: IO () %call %code int result = IImageUnlock(); %fail {result < 0} {getError();} %fun IImageGetDimension :: IO () %call %code int result = IImageGetDimension(); %fail {result < 0} {getError();} %fun IImageGetBitsPerPixel :: IO () %call %code int result = IImageGetBitsPerPixel(); %fail {result < 0} {getError();} %fun IImageGetBytesPerPixel :: IO () %call %code int result = IImageGetBytesPerPixel(); %fail {result < 0} {getError();} %fun IImageGetImageDataSizeInBytes :: IO () %call %code int result = IImageGetImageDataSizeInBytes(); %fail {result < 0} {getError();} %fun IImageGetImageDataSizeInPixels :: IO () %call %code int result = IImageGetImageDataSizeInPixels(); %fail {result < 0} {getError();} %fun IImageGetPixel :: Int -> Int -> IO () %call (int x) (int y) %code int result = IImageGetPixel(x, y); %fail {result < 0} {getError();} %fun IImageSetPixel :: Int -> Int -> Int -> Int -> IO () %call (int x) (int y) (int color) (int blend) %code int result = IImageSetPixel(x, y, color, blend); %fail {result < 0} {getError();} %fun IImageGetColorFormat :: IO () %call %code int result = IImageGetColorFormat(); %fail {result < 0} {getError();} %fun IImageGetRedMask :: IO () %call %code int result = IImageGetRedMask(); %fail {result < 0} {getError();} %fun IImageGetGreenMask :: IO () %call %code int result = IImageGetGreenMask(); %fail {result < 0} {getError();} %fun IImageGetBlueMask :: IO () %call %code int result = IImageGetBlueMask(); %fail {result < 0} {getError();} %fun IImageGetAlphaMask :: IO () %call %code int result = IImageGetAlphaMask(); %fail {result < 0} {getError();} %fun IImageGetPitch :: IO () %call %code int result = IImageGetPitch(); %fail {result < 0} {getError();} %fun IImageCopyToScaling :: Int -> Int -> Int -> Int -> Int -> IO () %call (int target) (int width) (int height) (int format) (int pitch) %code int result = IImageCopyToScaling(target, width, height, format, pitch); %fail {result < 0} {getError();} %fun IImageCopyToScaling :: Int -> IO () %call (int target) %code int result = IImageCopyToScaling(target); %fail {result < 0} {getError();} %fun IImageCopyTo :: Int -> Int -> IO () %call (int target) (int pos) %code int result = IImageCopyTo(target, pos); %fail {result < 0} {getError();} %fun IImageCopyTo :: Int -> Int -> Int -> Int -> IO () %call (int target) (int pos) (int sourceRect) (int clipRect) %code int result = IImageCopyTo(target, pos, sourceRect, clipRect); %fail {result < 0} {getError();} %fun IImageCopyToWithAlpha :: Int -> Int -> Int -> Int -> Int -> IO () %call (int target) (int pos) (int sourceRect) (int color) (int clipRect) %code int result = IImageCopyToWithAlpha(target, pos, sourceRect, color, clipRect); %fail {result < 0} {getError();} %fun IImageCopyToScalingBoxFilter :: Int -> Int -> Int -> IO () %call (int target) (int bias) (int blend) %code int result = IImageCopyToScalingBoxFilter(target, bias, blend); %fail {result < 0} {getError();} %fun IImageFill :: Int -> IO () %call (int color) %code int result = IImageFill(color); %fail {result < 0} {getError();} %fun IImageGetBitsPerPixelFromFormat :: Int -> IO () %call (int format) %code int result = IImageGetBitsPerPixelFromFormat(format); %fail {result < 0} {getError();} %fun IImageSwitch :: IO () %call %code int result = IImageSwitch(); %fail {result < 0} {getError();} %fun IImageIsRenderTargetOnlyFormat :: Int -> IO () %call (int format) %code int result = IImageIsRenderTargetOnlyFormat(format); %fail {result < 0} {getError();} %fun IImageSwitch :: IO () %call %code int result = IImageSwitch(); %fail {result < 0} {getError();} %fun IAnimatedMeshMD2GetFrameLoop :: Int -> Int -> Int -> Int -> IO () %call (int l) (int outBegin) (int outEnd) (int outFPS) %code int result = IAnimatedMeshMD2GetFrameLoop(l, outBegin, outEnd, outFPS); %fail {result < 0} {getError();} %fun IAnimatedMeshMD2GetFrameLoop :: Int -> Int -> Int -> Int -> IO () %call (int name) (int outBegin) (int outEnd) (int outFPS) %code int result = IAnimatedMeshMD2GetFrameLoop(name, outBegin, outEnd, outFPS); %fail {result < 0} {getError();} %fun IAnimatedMeshMD2GetAnimationCount :: IO () %call %code int result = IAnimatedMeshMD2GetAnimationCount(); %fail {result < 0} {getError();} %fun IAnimatedMeshMD2GetAnimationName :: Int -> IO () %call (int nr) %code int result = IAnimatedMeshMD2GetAnimationName(nr); %fail {result < 0} {getError();} %fun IIndexBufferGetData :: IO () %call %code int result = IIndexBufferGetData(); %fail {result < 0} {getError();} %fun IIndexBufferGetType :: IO () %call %code int result = IIndexBufferGetType(); %fail {result < 0} {getError();} %fun IIndexBufferSetType :: Int -> IO () %call (int IndexType) %code int result = IIndexBufferSetType(IndexType); %fail {result < 0} {getError();} %fun IIndexBufferStride :: IO () %call %code int result = IIndexBufferStride(); %fail {result < 0} {getError();} %fun IIndexBufferSize :: IO () %call %code int result = IIndexBufferSize(); %fail {result < 0} {getError();} %fun IIndexBufferPush_back :: Int -> IO () %call (int element) %code int result = IIndexBufferPush_back(element); %fail {result < 0} {getError();} %fun IIndexBufferOperator :: Int -> IO () %call (int index) %code int result = IIndexBufferOperator(index); %fail {result < 0} {getError();} %fun IIndexBufferGetLast :: IO () %call %code int result = IIndexBufferGetLast(); %fail {result < 0} {getError();} %fun IIndexBufferSetValue :: Int -> Int -> IO () %call (int index) (int value) %code int result = IIndexBufferSetValue(index, value); %fail {result < 0} {getError();} %fun IIndexBufferSet_used :: Int -> IO () %call (int usedNow) %code int result = IIndexBufferSet_used(usedNow); %fail {result < 0} {getError();} %fun IIndexBufferReallocate :: Int -> IO () %call (int new_size) %code int result = IIndexBufferReallocate(new_size); %fail {result < 0} {getError();} %fun IIndexBufferAllocated_size :: IO () %call %code int result = IIndexBufferAllocated_size(); %fail {result < 0} {getError();} %fun IIndexBufferPointer :: IO () %call %code int result = IIndexBufferPointer(); %fail {result < 0} {getError();} %fun IIndexBufferGetHardwareMappingHint :: IO () %call %code int result = IIndexBufferGetHardwareMappingHint(); %fail {result < 0} {getError();} %fun IIndexBufferSetHardwareMappingHint :: Int -> IO () %call (int NewMappingHint) %code int result = IIndexBufferSetHardwareMappingHint(NewMappingHint); %fail {result < 0} {getError();} %fun IIndexBufferSetDirty :: IO () %call %code int result = IIndexBufferSetDirty(); %fail {result < 0} {getError();} %fun IIndexBufferGetChangedID :: IO () %call %code int result = IIndexBufferGetChangedID(); %fail {result < 0} {getError();} %fun IVertexBufferGetData :: IO () %call %code int result = IVertexBufferGetData(); %fail {result < 0} {getError();} %fun IVertexBufferGetType :: IO () %call %code int result = IVertexBufferGetType(); %fail {result < 0} {getError();} %fun IVertexBufferSetType :: Int -> IO () %call (int vertexType) %code int result = IVertexBufferSetType(vertexType); %fail {result < 0} {getError();} %fun IVertexBufferStride :: IO () %call %code int result = IVertexBufferStride(); %fail {result < 0} {getError();} %fun IVertexBufferSize :: IO () %call %code int result = IVertexBufferSize(); %fail {result < 0} {getError();} %fun IVertexBufferPush_back :: Int -> IO () %call (int element) %code int result = IVertexBufferPush_back(element); %fail {result < 0} {getError();} %fun IVertexBufferOperator :: Int -> IO () %call (int index) %code int result = IVertexBufferOperator(index); %fail {result < 0} {getError();} %fun IVertexBufferGetLast :: IO () %call %code int result = IVertexBufferGetLast(); %fail {result < 0} {getError();} %fun IVertexBufferSet_used :: Int -> IO () %call (int usedNow) %code int result = IVertexBufferSet_used(usedNow); %fail {result < 0} {getError();} %fun IVertexBufferReallocate :: Int -> IO () %call (int new_size) %code int result = IVertexBufferReallocate(new_size); %fail {result < 0} {getError();} %fun IVertexBufferAllocated_size :: IO () %call %code int result = IVertexBufferAllocated_size(); %fail {result < 0} {getError();} %fun IVertexBufferPointer :: IO () %call %code int result = IVertexBufferPointer(); %fail {result < 0} {getError();} %fun IVertexBufferGetHardwareMappingHint :: IO () %call %code int result = IVertexBufferGetHardwareMappingHint(); %fail {result < 0} {getError();} %fun IVertexBufferSetHardwareMappingHint :: Int -> IO () %call (int NewMappingHint) %code int result = IVertexBufferSetHardwareMappingHint(NewMappingHint); %fail {result < 0} {getError();} %fun IVertexBufferSetDirty :: IO () %call %code int result = IVertexBufferSetDirty(); %fail {result < 0} {getError();} %fun IVertexBufferGetChangedID :: IO () %call %code int result = IVertexBufferGetChangedID(); %fail {result < 0} {getError();} %fun IWriteFileWrite :: Int -> Int -> IO () %call (int buffer) (int sizeToWrite) %code int result = IWriteFileWrite(buffer, sizeToWrite); %fail {result < 0} {getError();} %fun IWriteFileSeek :: Int -> Int -> IO () %call (int finalPos) (int relativeMovement) %code int result = IWriteFileSeek(finalPos, relativeMovement); %fail {result < 0} {getError();} %fun IWriteFileGetPos :: IO () %call %code int result = IWriteFileGetPos(); %fail {result < 0} {getError();} %fun IWriteFileGetFileName :: IO () %call %code int result = IWriteFileGetFileName(); %fail {result < 0} {getError();} %fun IWriteFileCreateWriteFile :: Int -> Int -> IO () %call (int fileName) (int append) %code int result = IWriteFileCreateWriteFile(fileName, append); %fail {result < 0} {getError();} %fun IImageWriterIsAWriteableFileExtension :: Int -> IO () %call (int filename) %code int result = IImageWriterIsAWriteableFileExtension(filename); %fail {result < 0} {getError();} %fun IImageWriterWriteImage :: Int -> Int -> Int -> IO () %call (int file) (int image) (int param) %code int result = IImageWriterWriteImage(file, image, param); %fail {result < 0} {getError();} %fun IReadFileRead :: Int -> Int -> IO () %call (int buffer) (int sizeToRead) %code int result = IReadFileRead(buffer, sizeToRead); %fail {result < 0} {getError();} %fun IReadFileSeek :: Int -> Int -> IO () %call (int finalPos) (int relativeMovement) %code int result = IReadFileSeek(finalPos, relativeMovement); %fail {result < 0} {getError();} %fun IReadFileGetSize :: IO () %call %code int result = IReadFileGetSize(); %fail {result < 0} {getError();} %fun IReadFileGetPos :: IO () %call %code int result = IReadFileGetPos(); %fail {result < 0} {getError();} %fun IReadFileGetFileName :: IO () %call %code int result = IReadFileGetFileName(); %fail {result < 0} {getError();} %fun IReadFileCreateReadFile :: Int -> IO () %call (int fileName) %code int result = IReadFileCreateReadFile(fileName); %fail {result < 0} {getError();} %fun IReadFileCreateLimitReadFile :: Int -> Int -> Int -> Int -> IO () %call (int fileName) (int alreadyOpenedFile) (int pos) (int areaSize) %code int result = IReadFileCreateLimitReadFile(fileName, alreadyOpenedFile, pos, areaSize); %fail {result < 0} {getError();} %fun IReadFileCreateMemoryReadFile :: Int -> Int -> Int -> Int -> IO () %call (int memory) (int size) (int fileName) (int deleteMemoryWhenDropped) %code int result = IReadFileCreateMemoryReadFile(memory, size, fileName, deleteMemoryWhenDropped); %fail {result < 0} {getError();} %fun IBillboardSceneNodeIBillboardSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int parent) %code int result = IBillboardSceneNodeIBillboardSceneNode(parent, mgr, id, position, parent); %fail {result < 0} {getError();} %fun IBillboardSceneNodeSetSize :: Int -> IO () %call (int size) %code int result = IBillboardSceneNodeSetSize(size); %fail {result < 0} {getError();} %fun IBillboardSceneNodeGetSize :: IO () %call %code int result = IBillboardSceneNodeGetSize(); %fail {result < 0} {getError();} %fun IBillboardSceneNodeSetColor :: Int -> IO () %call (int overallColor) %code int result = IBillboardSceneNodeSetColor(overallColor); %fail {result < 0} {getError();} %fun IBillboardSceneNodeSetColor :: Int -> Int -> IO () %call (int topColor) (int bottomColor) %code int result = IBillboardSceneNodeSetColor(topColor, bottomColor); %fail {result < 0} {getError();} %fun IBillboardSceneNodeGetColor :: Int -> Int -> IO () %call (int topColor) (int bottomColor) %code int result = IBillboardSceneNodeGetColor(topColor, bottomColor); %fail {result < 0} {getError();} %fun IAttributeExchangingObjectSerializeAttributes :: Int -> Int -> IO () %call (int out) (int options) %code int result = IAttributeExchangingObjectSerializeAttributes(out, options); %fail {result < 0} {getError();} %fun IAttributeExchangingObjectDeserializeAttributes :: Int -> Int -> IO () %call (int i_n) (int options) %code int result = IAttributeExchangingObjectDeserializeAttributes(i_n, options); %fail {result < 0} {getError();} %fun IParticleEmitterEmitt :: Int -> Int -> Int -> IO () %call (int now) (int timeSinceLastCall) (int outArray) %code int result = IParticleEmitterEmitt(now, timeSinceLastCall, outArray); %fail {result < 0} {getError();} %fun IParticleEmitterSetDirection :: Int -> IO () %call (int newDirection) %code int result = IParticleEmitterSetDirection(newDirection); %fail {result < 0} {getError();} %fun IParticleEmitterSetMinParticlesPerSecond :: Int -> IO () %call (int minPPS) %code int result = IParticleEmitterSetMinParticlesPerSecond(minPPS); %fail {result < 0} {getError();} %fun IParticleEmitterSetMaxParticlesPerSecond :: Int -> IO () %call (int maxPPS) %code int result = IParticleEmitterSetMaxParticlesPerSecond(maxPPS); %fail {result < 0} {getError();} %fun IParticleEmitterSetMinStartColor :: Int -> IO () %call (int color) %code int result = IParticleEmitterSetMinStartColor(color); %fail {result < 0} {getError();} %fun IParticleEmitterSetMaxStartColor :: Int -> IO () %call (int color) %code int result = IParticleEmitterSetMaxStartColor(color); %fail {result < 0} {getError();} %fun IParticleEmitterSetMaxStartSize :: Int -> IO () %call (int size) %code int result = IParticleEmitterSetMaxStartSize(size); %fail {result < 0} {getError();} %fun IParticleEmitterSetMinStartSize :: Int -> IO () %call (int size) %code int result = IParticleEmitterSetMinStartSize(size); %fail {result < 0} {getError();} %fun IParticleEmitterGetDirection :: IO () %call %code int result = IParticleEmitterGetDirection(); %fail {result < 0} {getError();} %fun IParticleEmitterGetMinParticlesPerSecond :: IO () %call %code int result = IParticleEmitterGetMinParticlesPerSecond(); %fail {result < 0} {getError();} %fun IParticleEmitterGetMaxParticlesPerSecond :: IO () %call %code int result = IParticleEmitterGetMaxParticlesPerSecond(); %fail {result < 0} {getError();} %fun IParticleEmitterGetMinStartColor :: IO () %call %code int result = IParticleEmitterGetMinStartColor(); %fail {result < 0} {getError();} %fun IParticleEmitterGetMaxStartColor :: IO () %call %code int result = IParticleEmitterGetMaxStartColor(); %fail {result < 0} {getError();} %fun IParticleEmitterGetMaxStartSize :: IO () %call %code int result = IParticleEmitterGetMaxStartSize(); %fail {result < 0} {getError();} %fun IParticleEmitterGetMinStartSize :: IO () %call %code int result = IParticleEmitterGetMinStartSize(); %fail {result < 0} {getError();} %fun IParticleEmitterGetType :: IO () %call %code int result = IParticleEmitterGetType(); %fail {result < 0} {getError();} %fun IIndexListIIndexList :: IO () %call %code int result = IIndexListIIndexList(); %fail {result < 0} {getError();} %fun IIndexListStride :: IO () %call %code int result = IIndexListStride(); %fail {result < 0} {getError();} %fun IIndexListSize :: IO () %call %code int result = IIndexListSize(); %fail {result < 0} {getError();} %fun IIndexListPush_back :: Int -> IO () %call (int element) %code int result = IIndexListPush_back(element); %fail {result < 0} {getError();} %fun IIndexListOperator :: Int -> IO () %call (int index) %code int result = IIndexListOperator(index); %fail {result < 0} {getError();} %fun IIndexListGetLast :: IO () %call %code int result = IIndexListGetLast(); %fail {result < 0} {getError();} %fun IIndexListSetValue :: Int -> Int -> IO () %call (int index) (int value) %code int result = IIndexListSetValue(index, value); %fail {result < 0} {getError();} %fun IIndexListSet_used :: Int -> IO () %call (int usedNow) %code int result = IIndexListSet_used(usedNow); %fail {result < 0} {getError();} %fun IIndexListReallocate :: Int -> IO () %call (int new_size) %code int result = IIndexListReallocate(new_size); %fail {result < 0} {getError();} %fun IIndexListAllocated_size :: IO () %call %code int result = IIndexListAllocated_size(); %fail {result < 0} {getError();} %fun IIndexListPointer :: IO () %call %code int result = IIndexListPointer(); %fail {result < 0} {getError();} %fun IIndexListGetType :: IO () %call %code int result = IIndexListGetType(); %fail {result < 0} {getError();} %fun IIndexListStride :: IO () %call %code int result = IIndexListStride(); %fail {result < 0} {getError();} %fun IIndexListSize :: IO () %call %code int result = IIndexListSize(); %fail {result < 0} {getError();} %fun IIndexListPush_back :: Int -> IO () %call (int element) %code int result = IIndexListPush_back(element); %fail {result < 0} {getError();} %fun IIndexListPush_back :: Int -> IO () %call (int element) %code int result = IIndexListPush_back(element); %fail {result < 0} {getError();} %fun IIndexListOperator :: Int -> IO () %call (int index) %code int result = IIndexListOperator(index); %fail {result < 0} {getError();} %fun IIndexListGetLast :: IO () %call %code int result = IIndexListGetLast(); %fail {result < 0} {getError();} %fun IIndexListSetValue :: Int -> Int -> IO () %call (int index) (int value) %code int result = IIndexListSetValue(index, value); %fail {result < 0} {getError();} %fun IIndexListSet_used :: Int -> IO () %call (int usedNow) %code int result = IIndexListSet_used(usedNow); %fail {result < 0} {getError();} %fun IIndexListSet_used :: IO () %call %code int result = IIndexListSet_used(); %fail {result < 0} {getError();} %fun IIndexListReallocate :: Int -> IO () %call (int new_size) %code int result = IIndexListReallocate(new_size); %fail {result < 0} {getError();} %fun IIndexListReallocate :: IO () %call %code int result = IIndexListReallocate(); %fail {result < 0} {getError();} %fun IIndexListAllocated_size :: IO () %call %code int result = IIndexListAllocated_size(); %fail {result < 0} {getError();} %fun IIndexListPointer :: IO () %call %code int result = IIndexListPointer(); %fail {result < 0} {getError();} %fun IIndexListGetType :: IO () %call %code int result = IIndexListGetType(); %fail {result < 0} {getError();} %fun IIndexListCIndexBuffer :: IO () %call %code int result = IIndexListCIndexBuffer(); %fail {result < 0} {getError();} %fun IIndexListSetType :: IO () %call %code int result = IIndexListSetType(); %fail {result < 0} {getError();} %fun IIndexListCIndexBuffer :: IO () %call %code int result = IIndexListCIndexBuffer(); %fail {result < 0} {getError();} %fun IIndexListSetType :: IO () %call %code int result = IIndexListSetType(); %fail {result < 0} {getError();} %fun IIndexListReallocate :: IO () %call %code int result = IIndexListReallocate(); %fail {result < 0} {getError();} %fun IIndexListSize :: IO () %call %code int result = IIndexListSize(); %fail {result < 0} {getError();} %fun IIndexListPush_back :: Int -> IO () %call (int n) %code int result = IIndexListPush_back(n); %fail {result < 0} {getError();} %fun IIndexListCIndexBuffer :: IO () %call %code int result = IIndexListCIndexBuffer(); %fail {result < 0} {getError();} %fun IIndexListSetType :: Int -> IO () %call (int IndexType) %code int result = IIndexListSetType(IndexType); %fail {result < 0} {getError();} %fun IIndexListSwitch :: IO () %call %code int result = IIndexListSwitch(); %fail {result < 0} {getError();} %fun IIndexListReallocate :: IO () %call %code int result = IIndexListReallocate(); %fail {result < 0} {getError();} %fun IIndexListSize :: IO () %call %code int result = IIndexListSize(); %fail {result < 0} {getError();} %fun IIndexListPush_back :: Int -> IO () %call (int n) %code int result = IIndexListPush_back(n); %fail {result < 0} {getError();} %fun IIndexListGetData :: IO () %call %code int result = IIndexListGetData(); %fail {result < 0} {getError();} %fun IIndexListGetType :: IO () %call %code int result = IIndexListGetType(); %fail {result < 0} {getError();} %fun IIndexListStride :: IO () %call %code int result = IIndexListStride(); %fail {result < 0} {getError();} %fun IIndexListSize :: IO () %call %code int result = IIndexListSize(); %fail {result < 0} {getError();} %fun IIndexListPush_back :: Int -> IO () %call (int element) %code int result = IIndexListPush_back(element); %fail {result < 0} {getError();} %fun IIndexListPush_back :: IO () %call %code int result = IIndexListPush_back(); %fail {result < 0} {getError();} %fun IIndexListOperator :: Int -> IO () %call (int index) %code int result = IIndexListOperator(index); %fail {result < 0} {getError();} %fun IIndexListGetLast :: IO () %call %code int result = IIndexListGetLast(); %fail {result < 0} {getError();} %fun IIndexListSetValue :: Int -> Int -> IO () %call (int index) (int value) %code int result = IIndexListSetValue(index, value); %fail {result < 0} {getError();} %fun IIndexListSetValue :: IO () %call %code int result = IIndexListSetValue(); %fail {result < 0} {getError();} %fun IIndexListSet_used :: Int -> IO () %call (int usedNow) %code int result = IIndexListSet_used(usedNow); %fail {result < 0} {getError();} %fun IIndexListSet_used :: IO () %call %code int result = IIndexListSet_used(); %fail {result < 0} {getError();} %fun IIndexListReallocate :: Int -> IO () %call (int new_size) %code int result = IIndexListReallocate(new_size); %fail {result < 0} {getError();} %fun IIndexListReallocate :: IO () %call %code int result = IIndexListReallocate(); %fail {result < 0} {getError();} %fun IIndexListAllocated_size :: IO () %call %code int result = IIndexListAllocated_size(); %fail {result < 0} {getError();} %fun IIndexListPointer :: IO () %call %code int result = IIndexListPointer(); %fail {result < 0} {getError();} %fun IIndexListGetHardwareMappingHint :: IO () %call %code int result = IIndexListGetHardwareMappingHint(); %fail {result < 0} {getError();} %fun IIndexListSetHardwareMappingHint :: Int -> IO () %call (int NewMappingHint) %code int result = IIndexListSetHardwareMappingHint(NewMappingHint); %fail {result < 0} {getError();} %fun IIndexListSetDirty :: IO () %call %code int result = IIndexListSetDirty(); %fail {result < 0} {getError();} %fun IIndexListGetChangedID :: IO () %call %code int result = IIndexListGetChangedID(); %fail {result < 0} {getError();} %fun IParticleAffectorIParticleAffector :: IO () %call %code int result = IParticleAffectorIParticleAffector(); %fail {result < 0} {getError();} %fun IParticleAffectorAffect :: Int -> Int -> Int -> IO () %call (int now) (int particlearray) (int count) %code int result = IParticleAffectorAffect(now, particlearray, count); %fail {result < 0} {getError();} %fun IParticleAffectorSetEnabled :: Int -> IO () %call (int enabled) %code int result = IParticleAffectorSetEnabled(enabled); %fail {result < 0} {getError();} %fun IParticleAffectorGetEnabled :: IO () %call %code int result = IParticleAffectorGetEnabled(); %fail {result < 0} {getError();} %fun IParticleAffectorGetType :: IO () %call %code int result = IParticleAffectorGetType(); %fail {result < 0} {getError();} %fun IParticleRotationAffectorSetPivotPoint :: Int -> IO () %call (int point) %code int result = IParticleRotationAffectorSetPivotPoint(point); %fail {result < 0} {getError();} %fun IParticleRotationAffectorSetSpeed :: Int -> IO () %call (int speed) %code int result = IParticleRotationAffectorSetSpeed(speed); %fail {result < 0} {getError();} %fun IParticleRotationAffectorGetPivotPoint :: IO () %call %code int result = IParticleRotationAffectorGetPivotPoint(); %fail {result < 0} {getError();} %fun IParticleRotationAffectorGetSpeed :: IO () %call %code int result = IParticleRotationAffectorGetSpeed(); %fail {result < 0} {getError();} %fun IParticleRotationAffectorGetType :: IO () %call %code int result = IParticleRotationAffectorGetType(); %fail {result < 0} {getError();} %fun IGUICheckBoxIGUICheckBox :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_CHECK_BOX) %code int result = IGUICheckBoxIGUICheckBox(environment, parent, id, EGUIET_CHECK_BOX); %fail {result < 0} {getError();} %fun IGUICheckBoxSetChecked :: Int -> IO () %call (int checked) %code int result = IGUICheckBoxSetChecked(checked); %fail {result < 0} {getError();} %fun IGUICheckBoxIsChecked :: IO () %call %code int result = IGUICheckBoxIsChecked(); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateCubeMesh :: Int -> IO () %call (int size) %code int result = IGeometryCreatorCreateCubeMesh(size); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateHillPlaneMesh :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int tileSize) (int tileCount) (int material) (int hillHeight) (int countHills) (int textureRepeatCount) %code int result = IGeometryCreatorCreateHillPlaneMesh(tileSize, tileCount, material, hillHeight, countHills, textureRepeatCount); %fail {result < 0} {getError();} %fun IGeometryCreatorCreatePlaneMesh :: Int -> Int -> Int -> Int -> IO () %call (int tileSize) (int tileCount) (int material) (int textureRepeatCount) %code int result = IGeometryCreatorCreatePlaneMesh(tileSize, tileCount, material, textureRepeatCount); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateTerrainMesh :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int texture) (int heightmap) (int stretchSize) (int maxHeight) (int driver) (int defaultVertexBlockSize) (int debugBorders) %code int result = IGeometryCreatorCreateTerrainMesh(texture, heightmap, stretchSize, maxHeight, driver, defaultVertexBlockSize, debugBorders); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateArrowMesh :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int tesselationCylinder) (int tesselationCone) (int height) (int cylinderHeight) (int widthCylinder) (int widthCone) (int colorCylinder) (int colorCone) %code int result = IGeometryCreatorCreateArrowMesh(tesselationCylinder, tesselationCone, height, cylinderHeight, widthCylinder, widthCone, colorCylinder, colorCone); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateSphereMesh :: Int -> Int -> Int -> IO () %call (int radius) (int polyCountX) (int polyCountY) %code int result = IGeometryCreatorCreateSphereMesh(radius, polyCountX, polyCountY); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateCylinderMesh :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int radius) (int length) (int tesselation) (int color) (int closeTop) (int oblique) %code int result = IGeometryCreatorCreateCylinderMesh(radius, length, tesselation, color, closeTop, oblique); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateConeMesh :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int radius) (int length) (int tesselation) (int colorTop) (int colorBottom) (int oblique) %code int result = IGeometryCreatorCreateConeMesh(radius, length, tesselation, colorTop, colorBottom, oblique); %fail {result < 0} {getError();} %fun IGeometryCreatorCreateVolumeLightMesh :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int subdivideU) (int subdivideV) (int footColor) (int tailColor) (int lpDistance) (int lightDim) %code int result = IGeometryCreatorCreateVolumeLightMesh(subdivideU, subdivideV, footColor, tailColor, lpDistance, lightDim); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeIBillboardTextSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int parent) %code int result = IBillboardTextSceneNodeIBillboardTextSceneNode(parent, mgr, id, position, parent); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeSetSize :: Int -> IO () %call (int size) %code int result = IBillboardTextSceneNodeSetSize(size); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeGetSize :: IO () %call %code int result = IBillboardTextSceneNodeGetSize(); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeSetColor :: Int -> IO () %call (int overallColor) %code int result = IBillboardTextSceneNodeSetColor(overallColor); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeSetColor :: Int -> Int -> IO () %call (int topColor) (int bottomColor) %code int result = IBillboardTextSceneNodeSetColor(topColor, bottomColor); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeGetColor :: Int -> Int -> IO () %call (int topColor) (int bottomColor) %code int result = IBillboardTextSceneNodeGetColor(topColor, bottomColor); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeSetText :: Int -> IO () %call (int text) %code int result = IBillboardTextSceneNodeSetText(text); %fail {result < 0} {getError();} %fun IBillboardTextSceneNodeSetTextColor :: Int -> IO () %call (int color) %code int result = IBillboardTextSceneNodeSetTextColor(color); %fail {result < 0} {getError();} %fun IParticleFadeOutAffectorSetTargetColor :: Int -> IO () %call (int targetColor) %code int result = IParticleFadeOutAffectorSetTargetColor(targetColor); %fail {result < 0} {getError();} %fun IParticleFadeOutAffectorSetFadeOutTime :: Int -> IO () %call (int fadeOutTime) %code int result = IParticleFadeOutAffectorSetFadeOutTime(fadeOutTime); %fail {result < 0} {getError();} %fun IParticleFadeOutAffectorGetTargetColor :: IO () %call %code int result = IParticleFadeOutAffectorGetTargetColor(); %fail {result < 0} {getError();} %fun IParticleFadeOutAffectorGetFadeOutTime :: IO () %call %code int result = IParticleFadeOutAffectorGetFadeOutTime(); %fail {result < 0} {getError();} %fun IParticleFadeOutAffectorGetType :: IO () %call %code int result = IParticleFadeOutAffectorGetType(); %fail {result < 0} {getError();} %fun IShadowVolumeSceneNodeIShadowVolumeSceneNode :: Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int parent) %code int result = IShadowVolumeSceneNodeIShadowVolumeSceneNode(parent, mgr, parent); %fail {result < 0} {getError();} %fun IShadowVolumeSceneNodeSetShadowMesh :: Int -> IO () %call (int mesh) %code int result = IShadowVolumeSceneNodeSetShadowMesh(mesh); %fail {result < 0} {getError();} %fun IShadowVolumeSceneNodeUpdateShadowVolumes :: IO () %call %code int result = IShadowVolumeSceneNodeUpdateShadowVolumes(); %fail {result < 0} {getError();} %fun IFileListGetFileCount :: IO () %call %code int result = IFileListGetFileCount(); %fail {result < 0} {getError();} %fun IFileListGetFileName :: Int -> IO () %call (int index) %code int result = IFileListGetFileName(index); %fail {result < 0} {getError();} %fun IFileListGetFullFileName :: Int -> IO () %call (int index) %code int result = IFileListGetFullFileName(index); %fail {result < 0} {getError();} %fun IFileListGetFileSize :: Int -> IO () %call (int index) %code int result = IFileListGetFileSize(index); %fail {result < 0} {getError();} %fun IFileListGetID :: Int -> IO () %call (int index) %code int result = IFileListGetID(index); %fail {result < 0} {getError();} %fun IFileListIsDirectory :: Int -> IO () %call (int index) %code int result = IFileListIsDirectory(index); %fail {result < 0} {getError();} %fun IFileListFindFile :: Int -> Int -> IO () %call (int filename) (int isFolder) %code int result = IFileListFindFile(filename, isFolder); %fail {result < 0} {getError();} %fun IFileListGetPath :: IO () %call %code int result = IFileListGetPath(); %fail {result < 0} {getError();} %fun IFileListAddItem :: Int -> Int -> Int -> Int -> IO () %call (int fullPath) (int size) (int isDirectory) (int id) %code int result = IFileListAddItem(fullPath, size, isDirectory, id); %fail {result < 0} {getError();} %fun IFileListSort :: IO () %call %code int result = IFileListSort(); %fail {result < 0} {getError();} %fun IMeshGetMeshBufferCount :: IO () %call %code int result = IMeshGetMeshBufferCount(); %fail {result < 0} {getError();} %fun IMeshGetMeshBuffer :: Int -> IO () %call (int nr) %code int result = IMeshGetMeshBuffer(nr); %fail {result < 0} {getError();} %fun IMeshGetMeshBuffer :: Int -> IO () %call (int material) %code int result = IMeshGetMeshBuffer(material); %fail {result < 0} {getError();} %fun IMeshGetBoundingBox :: IO () %call %code int result = IMeshGetBoundingBox(); %fail {result < 0} {getError();} %fun IMeshSetBoundingBox :: Int -> IO () %call (int box) %code int result = IMeshSetBoundingBox(box); %fail {result < 0} {getError();} %fun IMeshSetMaterialFlag :: Int -> Int -> IO () %call (int flag) (int newvalue) %code int result = IMeshSetMaterialFlag(flag, newvalue); %fail {result < 0} {getError();} %fun IMeshSetHardwareMappingHint :: Int -> Int -> IO () %call (int newMappingHint) (int buffer) %code int result = IMeshSetHardwareMappingHint(newMappingHint, buffer); %fail {result < 0} {getError();} %fun IMeshSetDirty :: Int -> IO () %call (int buffer) %code int result = IMeshSetDirty(buffer); %fail {result < 0} {getError();} %fun IrrlichtDeviceRun :: IO () %call %code int result = IrrlichtDeviceRun(); %fail {result < 0} {getError();} %fun IrrlichtDeviceYield :: IO () %call %code int result = IrrlichtDeviceYield(); %fail {result < 0} {getError();} %fun IrrlichtDeviceSleep :: Int -> Int -> IO () %call (int timeMs) (int pauseTimer) %code int result = IrrlichtDeviceSleep(timeMs, pauseTimer); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetVideoDriver :: IO () %call %code int result = IrrlichtDeviceGetVideoDriver(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetFileSystem :: IO () %call %code int result = IrrlichtDeviceGetFileSystem(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetGUIEnvironment :: IO () %call %code int result = IrrlichtDeviceGetGUIEnvironment(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetSceneManager :: IO () %call %code int result = IrrlichtDeviceGetSceneManager(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetCursorControl :: IO () %call %code int result = IrrlichtDeviceGetCursorControl(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetLogger :: IO () %call %code int result = IrrlichtDeviceGetLogger(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetVideoModeList :: IO () %call %code int result = IrrlichtDeviceGetVideoModeList(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetOSOperator :: IO () %call %code int result = IrrlichtDeviceGetOSOperator(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetTimer :: IO () %call %code int result = IrrlichtDeviceGetTimer(); %fail {result < 0} {getError();} %fun IrrlichtDeviceSetWindowCaption :: Int -> IO () %call (int text) %code int result = IrrlichtDeviceSetWindowCaption(text); %fail {result < 0} {getError();} %fun IrrlichtDeviceIsWindowActive :: IO () %call %code int result = IrrlichtDeviceIsWindowActive(); %fail {result < 0} {getError();} %fun IrrlichtDeviceIsWindowFocused :: IO () %call %code int result = IrrlichtDeviceIsWindowFocused(); %fail {result < 0} {getError();} %fun IrrlichtDeviceIsWindowMinimized :: IO () %call %code int result = IrrlichtDeviceIsWindowMinimized(); %fail {result < 0} {getError();} %fun IrrlichtDeviceIsFullscreen :: IO () %call %code int result = IrrlichtDeviceIsFullscreen(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetColorFormat :: IO () %call %code int result = IrrlichtDeviceGetColorFormat(); %fail {result < 0} {getError();} %fun IrrlichtDeviceCloseDevice :: IO () %call %code int result = IrrlichtDeviceCloseDevice(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetVersion :: IO () %call %code int result = IrrlichtDeviceGetVersion(); %fail {result < 0} {getError();} %fun IrrlichtDeviceSetEventReceiver :: Int -> IO () %call (int receiver) %code int result = IrrlichtDeviceSetEventReceiver(receiver); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetEventReceiver :: IO () %call %code int result = IrrlichtDeviceGetEventReceiver(); %fail {result < 0} {getError();} %fun IrrlichtDevicePostEventFromUser :: Int -> IO () %call (int event) %code int result = IrrlichtDevicePostEventFromUser(event); %fail {result < 0} {getError();} %fun IrrlichtDeviceSetInputReceivingSceneManager :: Int -> IO () %call (int sceneManager) %code int result = IrrlichtDeviceSetInputReceivingSceneManager(sceneManager); %fail {result < 0} {getError();} %fun IrrlichtDeviceSetResizable :: Int -> IO () %call (int resize) %code int result = IrrlichtDeviceSetResizable(resize); %fail {result < 0} {getError();} %fun IrrlichtDeviceMinimizeWindow :: IO () %call %code int result = IrrlichtDeviceMinimizeWindow(); %fail {result < 0} {getError();} %fun IrrlichtDeviceMaximizeWindow :: IO () %call %code int result = IrrlichtDeviceMaximizeWindow(); %fail {result < 0} {getError();} %fun IrrlichtDeviceRestoreWindow :: IO () %call %code int result = IrrlichtDeviceRestoreWindow(); %fail {result < 0} {getError();} %fun IrrlichtDeviceActivateJoysticks :: Int -> IO () %call (int joystickInfo) %code int result = IrrlichtDeviceActivateJoysticks(joystickInfo); %fail {result < 0} {getError();} %fun IrrlichtDeviceSetGammaRamp :: Int -> Int -> Int -> Int -> Int -> IO () %call (int red) (int green) (int blue) (int relativebrightness) (int relativecontrast) %code int result = IrrlichtDeviceSetGammaRamp(red, green, blue, relativebrightness, relativecontrast); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetGammaRamp :: Int -> Int -> Int -> Int -> Int -> IO () %call (int red) (int green) (int blue) (int brightness) (int contrast) %code int result = IrrlichtDeviceGetGammaRamp(red, green, blue, brightness, contrast); %fail {result < 0} {getError();} %fun IrrlichtDeviceClearSystemMessages :: IO () %call %code int result = IrrlichtDeviceClearSystemMessages(); %fail {result < 0} {getError();} %fun IrrlichtDeviceGetType :: IO () %call %code int result = IrrlichtDeviceGetType(); %fail {result < 0} {getError();} %fun IrrlichtDeviceIsDriverSupported :: Int -> IO () %call (int driver) %code int result = IrrlichtDeviceIsDriverSupported(driver); %fail {result < 0} {getError();} %fun IrrlichtDeviceSwitch :: IO () %call %code int result = IrrlichtDeviceSwitch(); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterSetAnimatedMeshSceneNode :: Int -> IO () %call (int node) %code int result = IParticleAnimatedMeshSceneNodeEmitterSetAnimatedMeshSceneNode(node); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterSetUseNormalDirection :: Int -> IO () %call (int useNormalDirection) %code int result = IParticleAnimatedMeshSceneNodeEmitterSetUseNormalDirection(useNormalDirection); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterSetNormalDirectionModifier :: Int -> IO () %call (int normalDirectionModifier) %code int result = IParticleAnimatedMeshSceneNodeEmitterSetNormalDirectionModifier(normalDirectionModifier); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterSetEveryMeshVertex :: Int -> IO () %call (int everyMeshVertex) %code int result = IParticleAnimatedMeshSceneNodeEmitterSetEveryMeshVertex(everyMeshVertex); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterGetAnimatedMeshSceneNode :: IO () %call %code int result = IParticleAnimatedMeshSceneNodeEmitterGetAnimatedMeshSceneNode(); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterIsUsingNormalDirection :: IO () %call %code int result = IParticleAnimatedMeshSceneNodeEmitterIsUsingNormalDirection(); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterGetNormalDirectionModifier :: IO () %call %code int result = IParticleAnimatedMeshSceneNodeEmitterGetNormalDirectionModifier(); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterGetEveryMeshVertex :: IO () %call %code int result = IParticleAnimatedMeshSceneNodeEmitterGetEveryMeshVertex(); %fail {result < 0} {getError();} %fun IParticleAnimatedMeshSceneNodeEmitterGetType :: IO () %call %code int result = IParticleAnimatedMeshSceneNodeEmitterGetType(); %fail {result < 0} {getError();} %fun SVertexColorGammaManipulatorSVertexColorGammaManipulator :: IO () %call %code int result = SVertexColorGammaManipulatorSVertexColorGammaManipulator(); %fail {result < 0} {getError();} %fun SVertexColorGammaManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorGammaManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorGammaManipulatorSetRed :: IO () %call %code int result = SVertexColorGammaManipulatorSetRed(); %fail {result < 0} {getError();} %fun SVertexColorGammaManipulatorSetGreen :: IO () %call %code int result = SVertexColorGammaManipulatorSetGreen(); %fail {result < 0} {getError();} %fun SVertexColorGammaManipulatorSetBlue :: IO () %call %code int result = SVertexColorGammaManipulatorSetBlue(); %fail {result < 0} {getError();} %fun SVertexColorSetManipulatorSVertexColorSetManipulator :: Int -> IO () %call (int color) %code int result = SVertexColorSetManipulatorSVertexColorSetManipulator(color); %fail {result < 0} {getError();} %fun SVertexColorSetManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorSetManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexTCoordsScaleManipulatorSVertexTCoordsScaleManipulator :: Int -> Int -> Int -> IO () %call (int factor) (int uvSet) (int uvSet) %code int result = SVertexTCoordsScaleManipulatorSVertexTCoordsScaleManipulator(factor, uvSet, uvSet); %fail {result < 0} {getError();} %fun SVertexTCoordsScaleManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexTCoordsScaleManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexTCoordsScaleManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexTCoordsScaleManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorBrightnessManipulatorSVertexColorBrightnessManipulator :: Int -> IO () %call (int amount) %code int result = SVertexColorBrightnessManipulatorSVertexColorBrightnessManipulator(amount); %fail {result < 0} {getError();} %fun SVertexColorBrightnessManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorBrightnessManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorBrightnessManipulatorSetRed :: Int -> Int -> IO () %call (int Amount) (int u) %code int result = SVertexColorBrightnessManipulatorSetRed(Amount, u); %fail {result < 0} {getError();} %fun SVertexColorBrightnessManipulatorSetGreen :: Int -> Int -> IO () %call (int Amount) (int u) %code int result = SVertexColorBrightnessManipulatorSetGreen(Amount, u); %fail {result < 0} {getError();} %fun SVertexColorBrightnessManipulatorSetBlue :: Int -> Int -> IO () %call (int Amount) (int u) %code int result = SVertexColorBrightnessManipulatorSetBlue(Amount, u); %fail {result < 0} {getError();} %fun SVertexColorSetAlphaManipulatorSVertexColorSetAlphaManipulator :: Int -> IO () %call (int alpha) %code int result = SVertexColorSetAlphaManipulatorSVertexColorSetAlphaManipulator(alpha); %fail {result < 0} {getError();} %fun SVertexColorSetAlphaManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorSetAlphaManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorSetAlphaManipulatorSetAlpha :: IO () %call %code int result = SVertexColorSetAlphaManipulatorSetAlpha(); %fail {result < 0} {getError();} %fun SVertexColorInvertManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorInvertManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorInvertManipulatorSetRed :: IO () %call %code int result = SVertexColorInvertManipulatorSetRed(); %fail {result < 0} {getError();} %fun SVertexColorInvertManipulatorSetGreen :: IO () %call %code int result = SVertexColorInvertManipulatorSetGreen(); %fail {result < 0} {getError();} %fun SVertexColorInvertManipulatorSetBlue :: IO () %call %code int result = SVertexColorInvertManipulatorSetBlue(); %fail {result < 0} {getError();} %fun SVertexColorInterpolateLinearManipulatorSVertexColorInterpolateLinearManipulator :: Int -> Int -> IO () %call (int color) (int factor) %code int result = SVertexColorInterpolateLinearManipulatorSVertexColorInterpolateLinearManipulator(color, factor); %fail {result < 0} {getError();} %fun SVertexColorInterpolateLinearManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorInterpolateLinearManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorInterpolateLinearManipulatorGetInterpolated :: IO () %call %code int result = SVertexColorInterpolateLinearManipulatorGetInterpolated(); %fail {result < 0} {getError();} %fun SVertexColorThresholdManipulatorSVertexColorThresholdManipulator :: Int -> Int -> Int -> IO () %call (int threshold) (int low) (int high) %code int result = SVertexColorThresholdManipulatorSVertexColorThresholdManipulator(threshold, low, high); %fail {result < 0} {getError();} %fun SVertexColorThresholdManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorThresholdManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorContrastManipulatorSVertexColorContrastManipulator :: Int -> IO () %call (int factor) %code int result = SVertexColorContrastManipulatorSVertexColorContrastManipulator(factor); %fail {result < 0} {getError();} %fun SVertexColorContrastManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorContrastManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorContrastManipulatorSetRed :: IO () %call %code int result = SVertexColorContrastManipulatorSetRed(); %fail {result < 0} {getError();} %fun SVertexColorContrastManipulatorSetGreen :: IO () %call %code int result = SVertexColorContrastManipulatorSetGreen(); %fail {result < 0} {getError();} %fun SVertexColorContrastManipulatorSetBlue :: IO () %call %code int result = SVertexColorContrastManipulatorSetBlue(); %fail {result < 0} {getError();} %fun SVertexPositionScaleManipulatorSVertexPositionScaleManipulator :: Int -> IO () %call (int factor) %code int result = SVertexPositionScaleManipulatorSVertexPositionScaleManipulator(factor); %fail {result < 0} {getError();} %fun SVertexPositionScaleManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexPositionScaleManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorContrastBrightnessManipulatorSVertexColorContrastBrightnessManipulator :: Int -> IO () %call (int factor) %code int result = SVertexColorContrastBrightnessManipulatorSVertexColorContrastBrightnessManipulator(factor); %fail {result < 0} {getError();} %fun SVertexColorContrastBrightnessManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorContrastBrightnessManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorContrastBrightnessManipulatorSetRed :: Int -> IO () %call (int Amount) %code int result = SVertexColorContrastBrightnessManipulatorSetRed(Amount); %fail {result < 0} {getError();} %fun SVertexColorContrastBrightnessManipulatorSetGreen :: Int -> IO () %call (int Amount) %code int result = SVertexColorContrastBrightnessManipulatorSetGreen(Amount); %fail {result < 0} {getError();} %fun SVertexColorContrastBrightnessManipulatorSetBlue :: Int -> IO () %call (int Amount) %code int result = SVertexColorContrastBrightnessManipulatorSetBlue(Amount); %fail {result < 0} {getError();} %fun SVertexColorScaleManipulatorSVertexColorScaleManipulator :: Int -> IO () %call (int factor) %code int result = SVertexColorScaleManipulatorSVertexColorScaleManipulator(factor); %fail {result < 0} {getError();} %fun SVertexColorScaleManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorScaleManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorScaleManipulatorSetRed :: IO () %call %code int result = SVertexColorScaleManipulatorSetRed(); %fail {result < 0} {getError();} %fun SVertexColorScaleManipulatorSetGreen :: IO () %call %code int result = SVertexColorScaleManipulatorSetGreen(); %fail {result < 0} {getError();} %fun SVertexColorScaleManipulatorSetBlue :: IO () %call %code int result = SVertexColorScaleManipulatorSetBlue(); %fail {result < 0} {getError();} %fun SVertexColorDesaturateToLuminanceManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorDesaturateToLuminanceManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorDesaturateToLuminanceManipulatorRound32 :: IO () %call %code int result = SVertexColorDesaturateToLuminanceManipulatorRound32(); %fail {result < 0} {getError();} %fun SVertexColorInterpolateQuadraticManipulatorSVertexColorInterpolateQuadraticManipulator :: Int -> Int -> Int -> IO () %call (int color1) (int color2) (int factor) %code int result = SVertexColorInterpolateQuadraticManipulatorSVertexColorInterpolateQuadraticManipulator(color1, color2, factor); %fail {result < 0} {getError();} %fun SVertexColorInterpolateQuadraticManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorInterpolateQuadraticManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorInterpolateQuadraticManipulatorGetInterpolated_quadratic :: IO () %call %code int result = SVertexColorInterpolateQuadraticManipulatorGetInterpolated_quadratic(); %fail {result < 0} {getError();} %fun SVertexColorDesaturateToLightnessManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorDesaturateToLightnessManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorDesaturateToLightnessManipulatorRound32 :: IO () %call %code int result = SVertexColorDesaturateToLightnessManipulatorRound32(); %fail {result < 0} {getError();} %fun SVertexColorDesaturateToAverageManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexColorDesaturateToAverageManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexColorDesaturateToAverageManipulatorGetAverage :: IO () %call %code int result = SVertexColorDesaturateToAverageManipulatorGetAverage(); %fail {result < 0} {getError();} %fun SVertexPositionScaleAlongNormalsManipulatorSVertexPositionScaleAlongNormalsManipulator :: Int -> IO () %call (int factor) %code int result = SVertexPositionScaleAlongNormalsManipulatorSVertexPositionScaleAlongNormalsManipulator(factor); %fail {result < 0} {getError();} %fun SVertexPositionScaleAlongNormalsManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexPositionScaleAlongNormalsManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexPositionTransformManipulatorSVertexPositionTransformManipulator :: Int -> IO () %call (int m) %code int result = SVertexPositionTransformManipulatorSVertexPositionTransformManipulator(m); %fail {result < 0} {getError();} %fun SVertexPositionTransformManipulatorOperator :: Int -> IO () %call (int vertex) %code int result = SVertexPositionTransformManipulatorOperator(vertex); %fail {result < 0} {getError();} %fun SVertexPositionTransformManipulatorTransformVect :: Int -> IO () %call (int Pos) %code int result = SVertexPositionTransformManipulatorTransformVect(Pos); %fail {result < 0} {getError();} %fun ITextureITexture :: Int -> IO () %call (int name) %code int result = ITextureITexture(name); %fail {result < 0} {getError();} %fun ITextureLock :: Int -> Int -> IO () %call (int readOnly) (int mipmapLevel) %code int result = ITextureLock(readOnly, mipmapLevel); %fail {result < 0} {getError();} %fun ITextureUnlock :: IO () %call %code int result = ITextureUnlock(); %fail {result < 0} {getError();} %fun ITextureGetOriginalSize :: IO () %call %code int result = ITextureGetOriginalSize(); %fail {result < 0} {getError();} %fun ITextureGetSize :: IO () %call %code int result = ITextureGetSize(); %fail {result < 0} {getError();} %fun ITextureGetDriverType :: IO () %call %code int result = ITextureGetDriverType(); %fail {result < 0} {getError();} %fun ITextureGetColorFormat :: IO () %call %code int result = ITextureGetColorFormat(); %fail {result < 0} {getError();} %fun ITextureGetPitch :: IO () %call %code int result = ITextureGetPitch(); %fail {result < 0} {getError();} %fun ITextureHasMipMaps :: IO () %call %code int result = ITextureHasMipMaps(); %fail {result < 0} {getError();} %fun ITextureHasAlpha :: IO () %call %code int result = ITextureHasAlpha(); %fail {result < 0} {getError();} %fun ITextureRegenerateMipMapLevels :: Int -> IO () %call (int mipmapData) %code int result = ITextureRegenerateMipMapLevels(mipmapData); %fail {result < 0} {getError();} %fun ITextureIsRenderTarget :: IO () %call %code int result = ITextureIsRenderTarget(); %fail {result < 0} {getError();} %fun ITextureGetName :: IO () %call %code int result = ITextureGetName(); %fail {result < 0} {getError();} %fun IAnimatedMeshGetFrameCount :: IO () %call %code int result = IAnimatedMeshGetFrameCount(); %fail {result < 0} {getError();} %fun IAnimatedMeshGetMesh :: Int -> Int -> Int -> Int -> IO () %call (int frame) (int detailLevel) (int startFrameLoop) (int endFrameLoop) %code int result = IAnimatedMeshGetMesh(frame, detailLevel, startFrameLoop, endFrameLoop); %fail {result < 0} {getError();} %fun IAnimatedMeshGetMeshType :: IO () %call %code int result = IAnimatedMeshGetMeshType(); %fail {result < 0} {getError();} %fun IGUIToolBarIGUIToolBar :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_TOOL_BAR) %code int result = IGUIToolBarIGUIToolBar(environment, parent, id, EGUIET_TOOL_BAR); %fail {result < 0} {getError();} %fun IGUIToolBarAddButton :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int id) (int text) (int tooltiptext) (int img) (int pressedimg) (int isPushButton) (int useAlphaChannel) %code int result = IGUIToolBarAddButton(id, text, tooltiptext, img, pressedimg, isPushButton, useAlphaChannel); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetCollisionPoint :: Int -> Int -> Int -> Int -> Int -> IO () %call (int ray) (int selector) (int outCollisionPoint) (int outTriangle) (int outNode) %code int result = ISceneCollisionManagerGetCollisionPoint(ray, selector, outCollisionPoint, outTriangle, outNode); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetCollisionResultPosition :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int selector) (int ellipsoidPosition) (int ellipsoidRadius) (int ellipsoidDirectionAndSpeed) (int triout) (int hitPosition) (int outFalling) (int outNode) (int slidingSpeed) (int gravityDirectionAndSpeed) %code int result = ISceneCollisionManagerGetCollisionResultPosition(selector, ellipsoidPosition, ellipsoidRadius, ellipsoidDirectionAndSpeed, triout, hitPosition, outFalling, outNode, slidingSpeed, gravityDirectionAndSpeed); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetRayFromScreenCoordinates :: Int -> Int -> IO () %call (int pos) (int camera) %code int result = ISceneCollisionManagerGetRayFromScreenCoordinates(pos, camera); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetScreenCoordinatesFrom3DPosition :: Int -> Int -> IO () %call (int pos) (int camera) %code int result = ISceneCollisionManagerGetScreenCoordinatesFrom3DPosition(pos, camera); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetSceneNodeFromScreenCoordinatesBB :: Int -> Int -> Int -> Int -> IO () %call (int pos) (int idBitMask) (int bNoDebugObjects) (int root) %code int result = ISceneCollisionManagerGetSceneNodeFromScreenCoordinatesBB(pos, idBitMask, bNoDebugObjects, root); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetSceneNodeFromRayBB :: Int -> Int -> Int -> Int -> IO () %call (int ray) (int idBitMask) (int bNoDebugObjects) (int root) %code int result = ISceneCollisionManagerGetSceneNodeFromRayBB(ray, idBitMask, bNoDebugObjects, root); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetSceneNodeFromCameraBB :: Int -> Int -> Int -> IO () %call (int camera) (int idBitMask) (int bNoDebugObjects) %code int result = ISceneCollisionManagerGetSceneNodeFromCameraBB(camera, idBitMask, bNoDebugObjects); %fail {result < 0} {getError();} %fun ISceneCollisionManagerGetSceneNodeAndCollisionPointFromRay :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int ray) (int outCollisionPoint) (int outTriangle) (int idBitMask) (int collisionRootNode) (int noDebugObjects) %code int result = ISceneCollisionManagerGetSceneNodeAndCollisionPointFromRay(ray, outCollisionPoint, outTriangle, idBitMask, collisionRootNode, noDebugObjects); %fail {result < 0} {getError();} %fun IGUIEnvironmentDrawAll :: IO () %call %code int result = IGUIEnvironmentDrawAll(); %fail {result < 0} {getError();} %fun IGUIEnvironmentSetFocus :: Int -> IO () %call (int element) %code int result = IGUIEnvironmentSetFocus(element); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetFocus :: IO () %call %code int result = IGUIEnvironmentGetFocus(); %fail {result < 0} {getError();} %fun IGUIEnvironmentRemoveFocus :: Int -> IO () %call (int element) %code int result = IGUIEnvironmentRemoveFocus(element); %fail {result < 0} {getError();} %fun IGUIEnvironmentHasFocus :: Int -> IO () %call (int element) %code int result = IGUIEnvironmentHasFocus(element); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetVideoDriver :: IO () %call %code int result = IGUIEnvironmentGetVideoDriver(); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetFileSystem :: IO () %call %code int result = IGUIEnvironmentGetFileSystem(); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetOSOperator :: IO () %call %code int result = IGUIEnvironmentGetOSOperator(); %fail {result < 0} {getError();} %fun IGUIEnvironmentClear :: IO () %call %code int result = IGUIEnvironmentClear(); %fail {result < 0} {getError();} %fun IGUIEnvironmentPostEventFromUser :: Int -> IO () %call (int event) %code int result = IGUIEnvironmentPostEventFromUser(event); %fail {result < 0} {getError();} %fun IGUIEnvironmentSetUserEventReceiver :: Int -> IO () %call (int evr) %code int result = IGUIEnvironmentSetUserEventReceiver(evr); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetSkin :: IO () %call %code int result = IGUIEnvironmentGetSkin(); %fail {result < 0} {getError();} %fun IGUIEnvironmentSetSkin :: Int -> IO () %call (int skin) %code int result = IGUIEnvironmentSetSkin(skin); %fail {result < 0} {getError();} %fun IGUIEnvironmentCreateSkin :: Int -> IO () %call (int type) %code int result = IGUIEnvironmentCreateSkin(type); %fail {result < 0} {getError();} %fun IGUIEnvironmentCreateImageList :: Int -> Int -> Int -> IO () %call (int texture) (int imageSize) (int useAlphaChannel) %code int result = IGUIEnvironmentCreateImageList(texture, imageSize, useAlphaChannel); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetFont :: Int -> IO () %call (int filename) %code int result = IGUIEnvironmentGetFont(filename); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddFont :: Int -> Int -> IO () %call (int name) (int font) %code int result = IGUIEnvironmentAddFont(name, font); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetBuiltInFont :: IO () %call %code int result = IGUIEnvironmentGetBuiltInFont(); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetSpriteBank :: Int -> IO () %call (int filename) %code int result = IGUIEnvironmentGetSpriteBank(filename); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddEmptySpriteBank :: Int -> IO () %call (int name) %code int result = IGUIEnvironmentAddEmptySpriteBank(name); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetRootGUIElement :: IO () %call %code int result = IGUIEnvironmentGetRootGUIElement(); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddButton :: Int -> Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) (int text) (int tooltiptext) %code int result = IGUIEnvironmentAddButton(rectangle, parent, id, text, tooltiptext); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddWindow :: Int -> Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int modal) (int text) (int parent) (int id) %code int result = IGUIEnvironmentAddWindow(rectangle, modal, text, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddModalScreen :: Int -> IO () %call (int parent) %code int result = IGUIEnvironmentAddModalScreen(parent); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddMessageBox :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int caption) (int text) (int modal) (int flags) (int parent) (int id) (int image) %code int result = IGUIEnvironmentAddMessageBox(caption, text, modal, flags, parent, id, image); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddScrollBar :: Int -> Int -> Int -> Int -> IO () %call (int horizontal) (int rectangle) (int parent) (int id) %code int result = IGUIEnvironmentAddScrollBar(horizontal, rectangle, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddImage :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int image) (int pos) (int useAlphaChannel) (int parent) (int id) (int text) %code int result = IGUIEnvironmentAddImage(image, pos, useAlphaChannel, parent, id, text); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddImage :: Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) (int text) %code int result = IGUIEnvironmentAddImage(rectangle, parent, id, text); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddCheckBox :: Int -> Int -> Int -> Int -> Int -> IO () %call (int checked) (int rectangle) (int parent) (int id) (int text) %code int result = IGUIEnvironmentAddCheckBox(checked, rectangle, parent, id, text); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddListBox :: Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) (int drawBackground) %code int result = IGUIEnvironmentAddListBox(rectangle, parent, id, drawBackground); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddTreeView :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) (int drawBackground) (int scrollBarVertical) (int scrollBarHorizontal) %code int result = IGUIEnvironmentAddTreeView(rectangle, parent, id, drawBackground, scrollBarVertical, scrollBarHorizontal); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddMeshViewer :: Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) (int text) %code int result = IGUIEnvironmentAddMeshViewer(rectangle, parent, id, text); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddFileOpenDialog :: Int -> Int -> Int -> Int -> IO () %call (int title) (int modal) (int parent) (int id) %code int result = IGUIEnvironmentAddFileOpenDialog(title, modal, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddColorSelectDialog :: Int -> Int -> Int -> Int -> IO () %call (int title) (int modal) (int parent) (int id) %code int result = IGUIEnvironmentAddColorSelectDialog(title, modal, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddStaticText :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int text) (int rectangle) (int border) (int wordWrap) (int parent) (int id) (int fillBackground) %code int result = IGUIEnvironmentAddStaticText(text, rectangle, border, wordWrap, parent, id, fillBackground); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddEditBox :: Int -> Int -> Int -> Int -> Int -> IO () %call (int text) (int rectangle) (int border) (int parent) (int id) %code int result = IGUIEnvironmentAddEditBox(text, rectangle, border, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddSpinBox :: Int -> Int -> Int -> Int -> Int -> IO () %call (int text) (int rectangle) (int border) (int parent) (int id) %code int result = IGUIEnvironmentAddSpinBox(text, rectangle, border, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddInOutFader :: Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) %code int result = IGUIEnvironmentAddInOutFader(rectangle, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddTabControl :: Int -> Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int fillbackground) (int border) (int id) %code int result = IGUIEnvironmentAddTabControl(rectangle, parent, fillbackground, border, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddTab :: Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) %code int result = IGUIEnvironmentAddTab(rectangle, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddContextMenu :: Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) %code int result = IGUIEnvironmentAddContextMenu(rectangle, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddMenu :: Int -> Int -> IO () %call (int parent) (int id) %code int result = IGUIEnvironmentAddMenu(parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddToolBar :: Int -> Int -> IO () %call (int parent) (int id) %code int result = IGUIEnvironmentAddToolBar(parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddComboBox :: Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) %code int result = IGUIEnvironmentAddComboBox(rectangle, parent, id); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddTable :: Int -> Int -> Int -> Int -> IO () %call (int rectangle) (int parent) (int id) (int drawBackground) %code int result = IGUIEnvironmentAddTable(rectangle, parent, id, drawBackground); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetDefaultGUIElementFactory :: IO () %call %code int result = IGUIEnvironmentGetDefaultGUIElementFactory(); %fail {result < 0} {getError();} %fun IGUIEnvironmentRegisterGUIElementFactory :: Int -> IO () %call (int factoryToAdd) %code int result = IGUIEnvironmentRegisterGUIElementFactory(factoryToAdd); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetRegisteredGUIElementFactoryCount :: IO () %call %code int result = IGUIEnvironmentGetRegisteredGUIElementFactoryCount(); %fail {result < 0} {getError();} %fun IGUIEnvironmentGetGUIElementFactory :: Int -> IO () %call (int index) %code int result = IGUIEnvironmentGetGUIElementFactory(index); %fail {result < 0} {getError();} %fun IGUIEnvironmentAddGUIElement :: Int -> Int -> IO () %call (int elementName) (int parent) %code int result = IGUIEnvironmentAddGUIElement(elementName, parent); %fail {result < 0} {getError();} %fun IGUIEnvironmentSaveGUI :: Int -> Int -> IO () %call (int filename) (int start) %code int result = IGUIEnvironmentSaveGUI(filename, start); %fail {result < 0} {getError();} %fun IGUIEnvironmentSaveGUI :: Int -> Int -> IO () %call (int file) (int start) %code int result = IGUIEnvironmentSaveGUI(file, start); %fail {result < 0} {getError();} %fun IGUIEnvironmentLoadGUI :: Int -> Int -> IO () %call (int filename) (int parent) %code int result = IGUIEnvironmentLoadGUI(filename, parent); %fail {result < 0} {getError();} %fun IGUIEnvironmentLoadGUI :: Int -> Int -> IO () %call (int file) (int parent) %code int result = IGUIEnvironmentLoadGUI(file, parent); %fail {result < 0} {getError();} %fun IGUIEnvironmentSerializeAttributes :: Int -> Int -> IO () %call (int out) (int options) %code int result = IGUIEnvironmentSerializeAttributes(out, options); %fail {result < 0} {getError();} %fun IGUIEnvironmentDeserializeAttributes :: Int -> Int -> IO () %call (int i_n) (int options) %code int result = IGUIEnvironmentDeserializeAttributes(i_n, options); %fail {result < 0} {getError();} %fun IGUIEnvironmentWriteGUIElement :: Int -> Int -> IO () %call (int writer) (int node) %code int result = IGUIEnvironmentWriteGUIElement(writer, node); %fail {result < 0} {getError();} %fun IGUIEnvironmentReadGUIElement :: Int -> Int -> IO () %call (int reader) (int node) %code int result = IGUIEnvironmentReadGUIElement(reader, node); %fail {result < 0} {getError();} %fun IGUIImageListIGUIImageList :: IO () %call %code int result = IGUIImageListIGUIImageList(); %fail {result < 0} {getError();} %fun IGUIImageListDraw :: Int -> Int -> Int -> IO () %call (int index) (int destPos) (int clip) %code int result = IGUIImageListDraw(index, destPos, clip); %fail {result < 0} {getError();} %fun IGUIImageListGetImageCount :: IO () %call %code int result = IGUIImageListGetImageCount(); %fail {result < 0} {getError();} %fun IGUIImageListGetImageSize :: IO () %call %code int result = IGUIImageListGetImageSize(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetOwner :: IO () %call %code int result = IGUITreeViewNodeGetOwner(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetParent :: IO () %call %code int result = IGUITreeViewNodeGetParent(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetText :: IO () %call %code int result = IGUITreeViewNodeGetText(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetText :: Int -> IO () %call (int text) %code int result = IGUITreeViewNodeSetText(text); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetIcon :: IO () %call %code int result = IGUITreeViewNodeGetIcon(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetIcon :: Int -> IO () %call (int icon) %code int result = IGUITreeViewNodeSetIcon(icon); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetImageIndex :: IO () %call %code int result = IGUITreeViewNodeGetImageIndex(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetImageIndex :: Int -> IO () %call (int imageIndex) %code int result = IGUITreeViewNodeSetImageIndex(imageIndex); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetSelectedImageIndex :: IO () %call %code int result = IGUITreeViewNodeGetSelectedImageIndex(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetSelectedImageIndex :: Int -> IO () %call (int imageIndex) %code int result = IGUITreeViewNodeSetSelectedImageIndex(imageIndex); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetData :: IO () %call %code int result = IGUITreeViewNodeGetData(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetData :: Int -> IO () %call (int data) %code int result = IGUITreeViewNodeSetData(data); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetData2 :: IO () %call %code int result = IGUITreeViewNodeGetData2(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetData2 :: Int -> IO () %call (int data) %code int result = IGUITreeViewNodeSetData2(data); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetChildCount :: IO () %call %code int result = IGUITreeViewNodeGetChildCount(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeClearChilds :: IO () %call %code int result = IGUITreeViewNodeClearChilds(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeHasChilds :: IO () %call %code int result = IGUITreeViewNodeHasChilds(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeAddChildBack :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int text) (int icon) (int imageIndex) (int selectedImageIndex) (int data) (int data2) %code int result = IGUITreeViewNodeAddChildBack(text, icon, imageIndex, selectedImageIndex, data, data2); %fail {result < 0} {getError();} %fun IGUITreeViewNodeAddChildFront :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int text) (int icon) (int imageIndex) (int selectedImageIndex) (int data) (int data2) %code int result = IGUITreeViewNodeAddChildFront(text, icon, imageIndex, selectedImageIndex, data, data2); %fail {result < 0} {getError();} %fun IGUITreeViewNodeInsertChildAfter :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int other) (int text) (int icon) (int imageIndex) (int selectedImageIndex) (int data) (int data2) %code int result = IGUITreeViewNodeInsertChildAfter(other, text, icon, imageIndex, selectedImageIndex, data, data2); %fail {result < 0} {getError();} %fun IGUITreeViewNodeInsertChildBefore :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int other) (int text) (int icon) (int imageIndex) (int selectedImageIndex) (int data) (int data2) %code int result = IGUITreeViewNodeInsertChildBefore(other, text, icon, imageIndex, selectedImageIndex, data, data2); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetFirstChild :: IO () %call %code int result = IGUITreeViewNodeGetFirstChild(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetLastChild :: IO () %call %code int result = IGUITreeViewNodeGetLastChild(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetPrevSibling :: IO () %call %code int result = IGUITreeViewNodeGetPrevSibling(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetNextSibling :: IO () %call %code int result = IGUITreeViewNodeGetNextSibling(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetNextVisible :: IO () %call %code int result = IGUITreeViewNodeGetNextVisible(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeDeleteChild :: Int -> IO () %call (int child) %code int result = IGUITreeViewNodeDeleteChild(child); %fail {result < 0} {getError();} %fun IGUITreeViewNodeMoveChildUp :: Int -> IO () %call (int child) %code int result = IGUITreeViewNodeMoveChildUp(child); %fail {result < 0} {getError();} %fun IGUITreeViewNodeMoveChildDown :: Int -> IO () %call (int child) %code int result = IGUITreeViewNodeMoveChildDown(child); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetExpanded :: IO () %call %code int result = IGUITreeViewNodeGetExpanded(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetExpanded :: Int -> IO () %call (int expanded) %code int result = IGUITreeViewNodeSetExpanded(expanded); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetSelected :: IO () %call %code int result = IGUITreeViewNodeGetSelected(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeSetSelected :: Int -> IO () %call (int selected) %code int result = IGUITreeViewNodeSetSelected(selected); %fail {result < 0} {getError();} %fun IGUITreeViewNodeIsRoot :: IO () %call %code int result = IGUITreeViewNodeIsRoot(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeGetLevel :: IO () %call %code int result = IGUITreeViewNodeGetLevel(); %fail {result < 0} {getError();} %fun IGUITreeViewNodeIsVisible :: IO () %call %code int result = IGUITreeViewNodeIsVisible(); %fail {result < 0} {getError();} %fun IGUITreeViewIGUITreeView :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_TREE_VIEW) %code int result = IGUITreeViewIGUITreeView(environment, parent, id, EGUIET_TREE_VIEW); %fail {result < 0} {getError();} %fun IGUITreeViewGetRoot :: IO () %call %code int result = IGUITreeViewGetRoot(); %fail {result < 0} {getError();} %fun IGUITreeViewGetSelected :: IO () %call %code int result = IGUITreeViewGetSelected(); %fail {result < 0} {getError();} %fun IGUITreeViewGetLinesVisible :: IO () %call %code int result = IGUITreeViewGetLinesVisible(); %fail {result < 0} {getError();} %fun IGUITreeViewSetLinesVisible :: Int -> IO () %call (int visible) %code int result = IGUITreeViewSetLinesVisible(visible); %fail {result < 0} {getError();} %fun IGUITreeViewSetIconFont :: Int -> IO () %call (int font) %code int result = IGUITreeViewSetIconFont(font); %fail {result < 0} {getError();} %fun IGUITreeViewSetImageList :: Int -> IO () %call (int imageList) %code int result = IGUITreeViewSetImageList(imageList); %fail {result < 0} {getError();} %fun IGUITreeViewGetImageList :: IO () %call %code int result = IGUITreeViewGetImageList(); %fail {result < 0} {getError();} %fun IGUITreeViewSetImageLeftOfIcon :: Int -> IO () %call (int bLeftOf) %code int result = IGUITreeViewSetImageLeftOfIcon(bLeftOf); %fail {result < 0} {getError();} %fun IGUITreeViewGetImageLeftOfIcon :: IO () %call %code int result = IGUITreeViewGetImageLeftOfIcon(); %fail {result < 0} {getError();} %fun IGUITreeViewGetLastEventNode :: IO () %call %code int result = IGUITreeViewGetLastEventNode(); %fail {result < 0} {getError();} %fun IGUIScrollBarIGUIScrollBar :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_SCROLL_BAR) %code int result = IGUIScrollBarIGUIScrollBar(environment, parent, id, EGUIET_SCROLL_BAR); %fail {result < 0} {getError();} %fun IGUIScrollBarSetMax :: Int -> IO () %call (int max) %code int result = IGUIScrollBarSetMax(max); %fail {result < 0} {getError();} %fun IGUIScrollBarGetMax :: IO () %call %code int result = IGUIScrollBarGetMax(); %fail {result < 0} {getError();} %fun IGUIScrollBarSetMin :: Int -> IO () %call (int min) %code int result = IGUIScrollBarSetMin(min); %fail {result < 0} {getError();} %fun IGUIScrollBarGetMin :: IO () %call %code int result = IGUIScrollBarGetMin(); %fail {result < 0} {getError();} %fun IGUIScrollBarGetSmallStep :: IO () %call %code int result = IGUIScrollBarGetSmallStep(); %fail {result < 0} {getError();} %fun IGUIScrollBarSetSmallStep :: Int -> IO () %call (int step) %code int result = IGUIScrollBarSetSmallStep(step); %fail {result < 0} {getError();} %fun IGUIScrollBarGetLargeStep :: IO () %call %code int result = IGUIScrollBarGetLargeStep(); %fail {result < 0} {getError();} %fun IGUIScrollBarSetLargeStep :: Int -> IO () %call (int step) %code int result = IGUIScrollBarSetLargeStep(step); %fail {result < 0} {getError();} %fun IGUIScrollBarGetPos :: IO () %call %code int result = IGUIScrollBarGetPos(); %fail {result < 0} {getError();} %fun IGUIScrollBarSetPos :: Int -> IO () %call (int pos) %code int result = IGUIScrollBarSetPos(pos); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeIVolumeLightSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int rotation) (int parent) %code int result = IVolumeLightSceneNodeIVolumeLightSceneNode(parent, mgr, id, position, rotation, parent); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeGetType :: IO () %call %code int result = IVolumeLightSceneNodeGetType(); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeSetSubDivideU :: Int -> IO () %call (int inU) %code int result = IVolumeLightSceneNodeSetSubDivideU(inU); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeSetSubDivideV :: Int -> IO () %call (int inV) %code int result = IVolumeLightSceneNodeSetSubDivideV(inV); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeGetSubDivideU :: IO () %call %code int result = IVolumeLightSceneNodeGetSubDivideU(); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeGetSubDivideV :: IO () %call %code int result = IVolumeLightSceneNodeGetSubDivideV(); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeSetFootColor :: Int -> IO () %call (int inColour) %code int result = IVolumeLightSceneNodeSetFootColor(inColour); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeSetTailColor :: Int -> IO () %call (int inColour) %code int result = IVolumeLightSceneNodeSetTailColor(inColour); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeGetFootColor :: IO () %call %code int result = IVolumeLightSceneNodeGetFootColor(); %fail {result < 0} {getError();} %fun IVolumeLightSceneNodeGetTailColor :: IO () %call %code int result = IVolumeLightSceneNodeGetTailColor(); %fail {result < 0} {getError();} %fun IGUIWindowIGUIWindow :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_WINDOW) %code int result = IGUIWindowIGUIWindow(environment, parent, id, EGUIET_WINDOW); %fail {result < 0} {getError();} %fun IGUIWindowGetCloseButton :: IO () %call %code int result = IGUIWindowGetCloseButton(); %fail {result < 0} {getError();} %fun IGUIWindowGetMinimizeButton :: IO () %call %code int result = IGUIWindowGetMinimizeButton(); %fail {result < 0} {getError();} %fun IGUIWindowGetMaximizeButton :: IO () %call %code int result = IGUIWindowGetMaximizeButton(); %fail {result < 0} {getError();} %fun IGUIWindowIsDraggable :: IO () %call %code int result = IGUIWindowIsDraggable(); %fail {result < 0} {getError();} %fun IGUIWindowSetDraggable :: Int -> IO () %call (int draggable) %code int result = IGUIWindowSetDraggable(draggable); %fail {result < 0} {getError();} %fun IGUIWindowSetDrawBackground :: Int -> IO () %call (int draw) %code int result = IGUIWindowSetDrawBackground(draw); %fail {result < 0} {getError();} %fun IGUIWindowGetDrawBackground :: IO () %call %code int result = IGUIWindowGetDrawBackground(); %fail {result < 0} {getError();} %fun IGUIWindowSetDrawTitlebar :: Int -> IO () %call (int draw) %code int result = IGUIWindowSetDrawTitlebar(draw); %fail {result < 0} {getError();} %fun IGUIWindowGetDrawTitlebar :: IO () %call %code int result = IGUIWindowGetDrawTitlebar(); %fail {result < 0} {getError();} %fun IGUIWindowGetClientRect :: IO () %call %code int result = IGUIWindowGetClientRect(); %fail {result < 0} {getError();} %fun IGUIFileOpenDialogIGUIFileOpenDialog :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_FILE_OPEN_DIALOG) %code int result = IGUIFileOpenDialogIGUIFileOpenDialog(environment, parent, id, EGUIET_FILE_OPEN_DIALOG); %fail {result < 0} {getError();} %fun IGUIFileOpenDialogGetFileName :: IO () %call %code int result = IGUIFileOpenDialogGetFileName(); %fail {result < 0} {getError();} %fun IGUIFileOpenDialogGetDirectoryName :: IO () %call %code int result = IGUIFileOpenDialogGetDirectoryName(); %fail {result < 0} {getError();} %fun IParticleBoxEmitterSetBox :: Int -> IO () %call (int box) %code int result = IParticleBoxEmitterSetBox(box); %fail {result < 0} {getError();} %fun IParticleBoxEmitterGetBox :: IO () %call %code int result = IParticleBoxEmitterGetBox(); %fail {result < 0} {getError();} %fun IParticleBoxEmitterGetType :: IO () %call %code int result = IParticleBoxEmitterGetType(); %fail {result < 0} {getError();} %fun ICursorControlSetVisible :: Int -> IO () %call (int visible) %code int result = ICursorControlSetVisible(visible); %fail {result < 0} {getError();} %fun ICursorControlIsVisible :: IO () %call %code int result = ICursorControlIsVisible(); %fail {result < 0} {getError();} %fun ICursorControlSetPosition :: Int -> IO () %call (int pos) %code int result = ICursorControlSetPosition(pos); %fail {result < 0} {getError();} %fun ICursorControlSetPosition :: Int -> Int -> IO () %call (int x) (int y) %code int result = ICursorControlSetPosition(x, y); %fail {result < 0} {getError();} %fun ICursorControlSetPosition :: Int -> IO () %call (int pos) %code int result = ICursorControlSetPosition(pos); %fail {result < 0} {getError();} %fun ICursorControlSetPosition :: Int -> Int -> IO () %call (int x) (int y) %code int result = ICursorControlSetPosition(x, y); %fail {result < 0} {getError();} %fun ICursorControlGetPosition :: IO () %call %code int result = ICursorControlGetPosition(); %fail {result < 0} {getError();} %fun ICursorControlGetRelativePosition :: IO () %call %code int result = ICursorControlGetRelativePosition(); %fail {result < 0} {getError();} %fun ICursorControlSetReferenceRect :: Int -> IO () %call (int rect) %code int result = ICursorControlSetReferenceRect(rect); %fail {result < 0} {getError();} %fun ICursorControlSetActiveIcon :: Int -> IO () %call (int iconId) %code int result = ICursorControlSetActiveIcon(iconId); %fail {result < 0} {getError();} %fun ICursorControlGetActiveIcon :: IO () %call %code int result = ICursorControlGetActiveIcon(); %fail {result < 0} {getError();} %fun ICursorControlAddIcon :: Int -> IO () %call (int icon) %code int result = ICursorControlAddIcon(icon); %fail {result < 0} {getError();} %fun ICursorControlChangeIcon :: Int -> Int -> IO () %call (int iconId) (int sprite) %code int result = ICursorControlChangeIcon(iconId, sprite); %fail {result < 0} {getError();} %fun ICursorControlGetSupportedIconSize :: IO () %call %code int result = ICursorControlGetSupportedIconSize(); %fail {result < 0} {getError();} %fun IBoneSceneNodeIBoneSceneNode :: Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) %code int result = IBoneSceneNodeIBoneSceneNode(parent, mgr, id); %fail {result < 0} {getError();} %fun IBoneSceneNodeGetBoneName :: IO () %call %code int result = IBoneSceneNodeGetBoneName(); %fail {result < 0} {getError();} %fun IBoneSceneNodeGetBoneIndex :: IO () %call %code int result = IBoneSceneNodeGetBoneIndex(); %fail {result < 0} {getError();} %fun IBoneSceneNodeSetAnimationMode :: Int -> IO () %call (int mode) %code int result = IBoneSceneNodeSetAnimationMode(mode); %fail {result < 0} {getError();} %fun IBoneSceneNodeGetAnimationMode :: IO () %call %code int result = IBoneSceneNodeGetAnimationMode(); %fail {result < 0} {getError();} %fun IBoneSceneNodeGetBoundingBox :: IO () %call %code int result = IBoneSceneNodeGetBoundingBox(); %fail {result < 0} {getError();} %fun IBoneSceneNodeOnAnimate :: Int -> IO () %call (int timeMs) %code int result = IBoneSceneNodeOnAnimate(timeMs); %fail {result < 0} {getError();} %fun IBoneSceneNodeRender :: IO () %call %code int result = IBoneSceneNodeRender(); %fail {result < 0} {getError();} %fun IBoneSceneNodeSetSkinningSpace :: Int -> IO () %call (int space) %code int result = IBoneSceneNodeSetSkinningSpace(space); %fail {result < 0} {getError();} %fun IBoneSceneNodeGetSkinningSpace :: IO () %call %code int result = IBoneSceneNodeGetSkinningSpace(); %fail {result < 0} {getError();} %fun IBoneSceneNodeUpdateAbsolutePositionOfAllChildren :: IO () %call %code int result = IBoneSceneNodeUpdateAbsolutePositionOfAllChildren(); %fail {result < 0} {getError();} %fun IMaterialRendererServicesIMaterialRendererServices :: IO () %call %code int result = IMaterialRendererServicesIMaterialRendererServices(); %fail {result < 0} {getError();} %fun IMaterialRendererServicesSetBasicRenderStates :: Int -> Int -> Int -> IO () %call (int material) (int lastMaterial) (int resetAllRenderstates) %code int result = IMaterialRendererServicesSetBasicRenderStates(material, lastMaterial, resetAllRenderstates); %fail {result < 0} {getError();} %fun IMaterialRendererServicesSetVertexShaderConstant :: Int -> Int -> Int -> IO () %call (int name) (int floats) (int count) %code int result = IMaterialRendererServicesSetVertexShaderConstant(name, floats, count); %fail {result < 0} {getError();} %fun IMaterialRendererServicesSetVertexShaderConstant :: Int -> Int -> Int -> IO () %call (int data) (int startRegister) (int constantAmount) %code int result = IMaterialRendererServicesSetVertexShaderConstant(data, startRegister, constantAmount); %fail {result < 0} {getError();} %fun IMaterialRendererServicesSetPixelShaderConstant :: Int -> Int -> Int -> IO () %call (int name) (int floats) (int count) %code int result = IMaterialRendererServicesSetPixelShaderConstant(name, floats, count); %fail {result < 0} {getError();} %fun IMaterialRendererServicesSetPixelShaderConstant :: Int -> Int -> Int -> IO () %call (int data) (int startRegister) (int constantAmount) %code int result = IMaterialRendererServicesSetPixelShaderConstant(data, startRegister, constantAmount); %fail {result < 0} {getError();} %fun IMaterialRendererServicesGetVideoDriver :: IO () %call %code int result = IMaterialRendererServicesGetVideoDriver(); %fail {result < 0} {getError();} %fun IVertexListIVertexList :: IO () %call %code int result = IVertexListIVertexList(); %fail {result < 0} {getError();} %fun IVertexListStride :: IO () %call %code int result = IVertexListStride(); %fail {result < 0} {getError();} %fun IVertexListSize :: IO () %call %code int result = IVertexListSize(); %fail {result < 0} {getError();} %fun IVertexListPush_back :: Int -> IO () %call (int element) %code int result = IVertexListPush_back(element); %fail {result < 0} {getError();} %fun IVertexListOperator :: Int -> IO () %call (int index) %code int result = IVertexListOperator(index); %fail {result < 0} {getError();} %fun IVertexListGetLast :: IO () %call %code int result = IVertexListGetLast(); %fail {result < 0} {getError();} %fun IVertexListSet_used :: Int -> IO () %call (int usedNow) %code int result = IVertexListSet_used(usedNow); %fail {result < 0} {getError();} %fun IVertexListReallocate :: Int -> IO () %call (int new_size) %code int result = IVertexListReallocate(new_size); %fail {result < 0} {getError();} %fun IVertexListAllocated_size :: IO () %call %code int result = IVertexListAllocated_size(); %fail {result < 0} {getError();} %fun IVertexListPointer :: IO () %call %code int result = IVertexListPointer(); %fail {result < 0} {getError();} %fun IVertexListGetType :: IO () %call %code int result = IVertexListGetType(); %fail {result < 0} {getError();} %fun IVertexListStride :: IO () %call %code int result = IVertexListStride(); %fail {result < 0} {getError();} %fun IVertexListSize :: IO () %call %code int result = IVertexListSize(); %fail {result < 0} {getError();} %fun IVertexListPush_back :: Int -> IO () %call (int element) %code int result = IVertexListPush_back(element); %fail {result < 0} {getError();} %fun IVertexListPush_back :: Int -> IO () %call (int element) %code int result = IVertexListPush_back(element); %fail {result < 0} {getError();} %fun IVertexListOperator :: Int -> IO () %call (int index) %code int result = IVertexListOperator(index); %fail {result < 0} {getError();} %fun IVertexListGetLast :: IO () %call %code int result = IVertexListGetLast(); %fail {result < 0} {getError();} %fun IVertexListSet_used :: Int -> IO () %call (int usedNow) %code int result = IVertexListSet_used(usedNow); %fail {result < 0} {getError();} %fun IVertexListSet_used :: IO () %call %code int result = IVertexListSet_used(); %fail {result < 0} {getError();} %fun IVertexListReallocate :: Int -> IO () %call (int new_size) %code int result = IVertexListReallocate(new_size); %fail {result < 0} {getError();} %fun IVertexListReallocate :: IO () %call %code int result = IVertexListReallocate(); %fail {result < 0} {getError();} %fun IVertexListAllocated_size :: IO () %call %code int result = IVertexListAllocated_size(); %fail {result < 0} {getError();} %fun IVertexListPointer :: IO () %call %code int result = IVertexListPointer(); %fail {result < 0} {getError();} %fun IVertexListGetType :: IO () %call %code int result = IVertexListGetType(); %fail {result < 0} {getError();} %fun IVertexListCVertexBuffer :: IO () %call %code int result = IVertexListCVertexBuffer(); %fail {result < 0} {getError();} %fun IVertexListSetType :: IO () %call %code int result = IVertexListSetType(); %fail {result < 0} {getError();} %fun IVertexListCVertexBuffer :: IO () %call %code int result = IVertexListCVertexBuffer(); %fail {result < 0} {getError();} %fun IVertexListSetType :: IO () %call %code int result = IVertexListSetType(); %fail {result < 0} {getError();} %fun IVertexListReallocate :: IO () %call %code int result = IVertexListReallocate(); %fail {result < 0} {getError();} %fun IVertexListSize :: IO () %call %code int result = IVertexListSize(); %fail {result < 0} {getError();} %fun IVertexListPush_back :: Int -> IO () %call (int n) %code int result = IVertexListPush_back(n); %fail {result < 0} {getError();} %fun IVertexListCVertexBuffer :: IO () %call %code int result = IVertexListCVertexBuffer(); %fail {result < 0} {getError();} %fun IVertexListSetType :: Int -> IO () %call (int vertexType) %code int result = IVertexListSetType(vertexType); %fail {result < 0} {getError();} %fun IVertexListSwitch :: IO () %call %code int result = IVertexListSwitch(); %fail {result < 0} {getError();} %fun IVertexListReallocate :: IO () %call %code int result = IVertexListReallocate(); %fail {result < 0} {getError();} %fun IVertexListSize :: IO () %call %code int result = IVertexListSize(); %fail {result < 0} {getError();} %fun IVertexListPush_back :: Int -> IO () %call (int n) %code int result = IVertexListPush_back(n); %fail {result < 0} {getError();} %fun IVertexListGetData :: IO () %call %code int result = IVertexListGetData(); %fail {result < 0} {getError();} %fun IVertexListGetType :: IO () %call %code int result = IVertexListGetType(); %fail {result < 0} {getError();} %fun IVertexListStride :: IO () %call %code int result = IVertexListStride(); %fail {result < 0} {getError();} %fun IVertexListSize :: IO () %call %code int result = IVertexListSize(); %fail {result < 0} {getError();} %fun IVertexListPush_back :: Int -> IO () %call (int element) %code int result = IVertexListPush_back(element); %fail {result < 0} {getError();} %fun IVertexListPush_back :: IO () %call %code int result = IVertexListPush_back(); %fail {result < 0} {getError();} %fun IVertexListOperator :: Int -> IO () %call (int index) %code int result = IVertexListOperator(index); %fail {result < 0} {getError();} %fun IVertexListGetLast :: IO () %call %code int result = IVertexListGetLast(); %fail {result < 0} {getError();} %fun IVertexListSet_used :: Int -> IO () %call (int usedNow) %code int result = IVertexListSet_used(usedNow); %fail {result < 0} {getError();} %fun IVertexListSet_used :: IO () %call %code int result = IVertexListSet_used(); %fail {result < 0} {getError();} %fun IVertexListReallocate :: Int -> IO () %call (int new_size) %code int result = IVertexListReallocate(new_size); %fail {result < 0} {getError();} %fun IVertexListReallocate :: IO () %call %code int result = IVertexListReallocate(); %fail {result < 0} {getError();} %fun IVertexListAllocated_size :: IO () %call %code int result = IVertexListAllocated_size(); %fail {result < 0} {getError();} %fun IVertexListPointer :: IO () %call %code int result = IVertexListPointer(); %fail {result < 0} {getError();} %fun IVertexListGetHardwareMappingHint :: IO () %call %code int result = IVertexListGetHardwareMappingHint(); %fail {result < 0} {getError();} %fun IVertexListSetHardwareMappingHint :: Int -> IO () %call (int NewMappingHint) %code int result = IVertexListSetHardwareMappingHint(NewMappingHint); %fail {result < 0} {getError();} %fun IVertexListSetDirty :: IO () %call %code int result = IVertexListSetDirty(); %fail {result < 0} {getError();} %fun IVertexListGetChangedID :: IO () %call %code int result = IVertexListGetChangedID(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraFPSGetMoveSpeed :: IO () %call %code int result = ISceneNodeAnimatorCameraFPSGetMoveSpeed(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraFPSSetMoveSpeed :: Int -> IO () %call (int moveSpeed) %code int result = ISceneNodeAnimatorCameraFPSSetMoveSpeed(moveSpeed); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraFPSGetRotateSpeed :: IO () %call %code int result = ISceneNodeAnimatorCameraFPSGetRotateSpeed(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraFPSSetRotateSpeed :: Int -> IO () %call (int rotateSpeed) %code int result = ISceneNodeAnimatorCameraFPSSetRotateSpeed(rotateSpeed); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraFPSSetKeyMap :: Int -> Int -> IO () %call (int map) (int count) %code int result = ISceneNodeAnimatorCameraFPSSetKeyMap(map, count); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraFPSSetVerticalMovement :: Int -> IO () %call (int allow) %code int result = ISceneNodeAnimatorCameraFPSSetVerticalMovement(allow); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCameraFPSSetInvertMouse :: Int -> IO () %call (int invert) %code int result = ISceneNodeAnimatorCameraFPSSetInvertMouse(invert); %fail {result < 0} {getError();} %fun IGUITabIGUITab :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_TAB) %code int result = IGUITabIGUITab(environment, parent, id, EGUIET_TAB); %fail {result < 0} {getError();} %fun IGUITabGetNumber :: IO () %call %code int result = IGUITabGetNumber(); %fail {result < 0} {getError();} %fun IGUITabSetDrawBackground :: Int -> IO () %call (int draw) %code int result = IGUITabSetDrawBackground(draw); %fail {result < 0} {getError();} %fun IGUITabSetBackgroundColor :: Int -> IO () %call (int c) %code int result = IGUITabSetBackgroundColor(c); %fail {result < 0} {getError();} %fun IGUITabIsDrawingBackground :: IO () %call %code int result = IGUITabIsDrawingBackground(); %fail {result < 0} {getError();} %fun IGUITabGetBackgroundColor :: IO () %call %code int result = IGUITabGetBackgroundColor(); %fail {result < 0} {getError();} %fun IGUITabSetTextColor :: Int -> IO () %call (int c) %code int result = IGUITabSetTextColor(c); %fail {result < 0} {getError();} %fun IGUITabGetTextColor :: IO () %call %code int result = IGUITabGetTextColor(); %fail {result < 0} {getError();} %fun IGUITabControlIGUITabControl :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_TAB_CONTROL) %code int result = IGUITabControlIGUITabControl(environment, parent, id, EGUIET_TAB_CONTROL); %fail {result < 0} {getError();} %fun IGUITabControlAddTab :: Int -> Int -> IO () %call (int caption) (int id) %code int result = IGUITabControlAddTab(caption, id); %fail {result < 0} {getError();} %fun IGUITabControlGetTabCount :: IO () %call %code int result = IGUITabControlGetTabCount(); %fail {result < 0} {getError();} %fun IGUITabControlGetTab :: Int -> IO () %call (int idx) %code int result = IGUITabControlGetTab(idx); %fail {result < 0} {getError();} %fun IGUITabControlSetActiveTab :: Int -> IO () %call (int idx) %code int result = IGUITabControlSetActiveTab(idx); %fail {result < 0} {getError();} %fun IGUITabControlSetActiveTab :: Int -> IO () %call (int tab) %code int result = IGUITabControlSetActiveTab(tab); %fail {result < 0} {getError();} %fun IGUITabControlGetActiveTab :: IO () %call %code int result = IGUITabControlGetActiveTab(); %fail {result < 0} {getError();} %fun IGUITabControlSetTabHeight :: Int -> IO () %call (int height) %code int result = IGUITabControlSetTabHeight(height); %fail {result < 0} {getError();} %fun IGUITabControlGetTabHeight :: IO () %call %code int result = IGUITabControlGetTabHeight(); %fail {result < 0} {getError();} %fun IGUITabControlSetTabMaxWidth :: Int -> IO () %call (int width) %code int result = IGUITabControlSetTabMaxWidth(width); %fail {result < 0} {getError();} %fun IGUITabControlGetTabMaxWidth :: IO () %call %code int result = IGUITabControlGetTabMaxWidth(); %fail {result < 0} {getError();} %fun IGUITabControlSetTabVerticalAlignment :: Int -> IO () %call (int alignment) %code int result = IGUITabControlSetTabVerticalAlignment(alignment); %fail {result < 0} {getError();} %fun IGUITabControlGetTabVerticalAlignment :: IO () %call %code int result = IGUITabControlGetTabVerticalAlignment(); %fail {result < 0} {getError();} %fun IGUITabControlSetTabExtraWidth :: Int -> IO () %call (int extraWidth) %code int result = IGUITabControlSetTabExtraWidth(extraWidth); %fail {result < 0} {getError();} %fun IGUITabControlGetTabExtraWidth :: IO () %call %code int result = IGUITabControlGetTabExtraWidth(); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterSetCenter :: Int -> IO () %call (int center) %code int result = IParticleCylinderEmitterSetCenter(center); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterSetNormal :: Int -> IO () %call (int normal) %code int result = IParticleCylinderEmitterSetNormal(normal); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterSetRadius :: Int -> IO () %call (int radius) %code int result = IParticleCylinderEmitterSetRadius(radius); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterSetLength :: Int -> IO () %call (int length) %code int result = IParticleCylinderEmitterSetLength(length); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterSetOutlineOnly :: Int -> IO () %call (int outlineOnly) %code int result = IParticleCylinderEmitterSetOutlineOnly(outlineOnly); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterGetCenter :: IO () %call %code int result = IParticleCylinderEmitterGetCenter(); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterGetNormal :: IO () %call %code int result = IParticleCylinderEmitterGetNormal(); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterGetRadius :: IO () %call %code int result = IParticleCylinderEmitterGetRadius(); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterGetLength :: IO () %call %code int result = IParticleCylinderEmitterGetLength(); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterGetOutlineOnly :: IO () %call %code int result = IParticleCylinderEmitterGetOutlineOnly(); %fail {result < 0} {getError();} %fun IParticleCylinderEmitterGetType :: IO () %call %code int result = IParticleCylinderEmitterGetType(); %fail {result < 0} {getError();} %fun IGUISpriteBankGetPositions :: IO () %call %code int result = IGUISpriteBankGetPositions(); %fail {result < 0} {getError();} %fun IGUISpriteBankGetSprites :: IO () %call %code int result = IGUISpriteBankGetSprites(); %fail {result < 0} {getError();} %fun IGUISpriteBankGetTextureCount :: IO () %call %code int result = IGUISpriteBankGetTextureCount(); %fail {result < 0} {getError();} %fun IGUISpriteBankGetTexture :: Int -> IO () %call (int index) %code int result = IGUISpriteBankGetTexture(index); %fail {result < 0} {getError();} %fun IGUISpriteBankAddTexture :: Int -> IO () %call (int texture) %code int result = IGUISpriteBankAddTexture(texture); %fail {result < 0} {getError();} %fun IGUISpriteBankSetTexture :: Int -> Int -> IO () %call (int index) (int texture) %code int result = IGUISpriteBankSetTexture(index, texture); %fail {result < 0} {getError();} %fun IGUISpriteBankAddTextureAsSprite :: Int -> IO () %call (int texture) %code int result = IGUISpriteBankAddTextureAsSprite(texture); %fail {result < 0} {getError();} %fun IGUISpriteBankClear :: IO () %call %code int result = IGUISpriteBankClear(); %fail {result < 0} {getError();} %fun IGUISpriteBankDraw2DSprite :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int index) (int pos) (int clip) (int color) (int starttime) (int currenttime) (int loop) (int center) %code int result = IGUISpriteBankDraw2DSprite(index, pos, clip, color, starttime, currenttime, loop, center); %fail {result < 0} {getError();} %fun IGUISpriteBankDraw2DSpriteBatch :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int indices) (int pos) (int clip) (int color) (int starttime) (int currenttime) (int loop) (int center) %code int result = IGUISpriteBankDraw2DSpriteBatch(indices, pos, clip, color, starttime, currenttime, loop, center); %fail {result < 0} {getError();} %fun IMetaTriangleSelectorAddTriangleSelector :: Int -> IO () %call (int toAdd) %code int result = IMetaTriangleSelectorAddTriangleSelector(toAdd); %fail {result < 0} {getError();} %fun IMetaTriangleSelectorRemoveTriangleSelector :: Int -> IO () %call (int toRemove) %code int result = IMetaTriangleSelectorRemoveTriangleSelector(toRemove); %fail {result < 0} {getError();} %fun IMetaTriangleSelectorRemoveAllTriangleSelectors :: IO () %call %code int result = IMetaTriangleSelectorRemoveAllTriangleSelectors(); %fail {result < 0} {getError();} %fun IGUIImageIGUIImage :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_IMAGE) %code int result = IGUIImageIGUIImage(environment, parent, id, EGUIET_IMAGE); %fail {result < 0} {getError();} %fun IGUIImageSetImage :: Int -> IO () %call (int image) %code int result = IGUIImageSetImage(image); %fail {result < 0} {getError();} %fun IGUIImageSetColor :: Int -> IO () %call (int color) %code int result = IGUIImageSetColor(color); %fail {result < 0} {getError();} %fun IGUIImageSetScaleImage :: Int -> IO () %call (int scale) %code int result = IGUIImageSetScaleImage(scale); %fail {result < 0} {getError();} %fun IGUIImageSetUseAlphaChannel :: Int -> IO () %call (int use) %code int result = IGUIImageSetUseAlphaChannel(use); %fail {result < 0} {getError();} %fun IGUIImageIsImageScaled :: IO () %call %code int result = IGUIImageIsImageScaled(); %fail {result < 0} {getError();} %fun IGUIImageIsAlphaChannelUsed :: IO () %call %code int result = IGUIImageIsAlphaChannelUsed(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeIAnimatedMeshSceneNode :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int rotation) (int scale) (int parent) %code int result = IAnimatedMeshSceneNodeIAnimatedMeshSceneNode(parent, mgr, id, position, rotation, scale, parent); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeIAnimatedMeshSceneNode :: IO () %call %code int result = IAnimatedMeshSceneNodeIAnimatedMeshSceneNode(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetCurrentFrame :: Int -> IO () %call (int frame) %code int result = IAnimatedMeshSceneNodeSetCurrentFrame(frame); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetFrameLoop :: Int -> Int -> IO () %call (int begin) (int end) %code int result = IAnimatedMeshSceneNodeSetFrameLoop(begin, end); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetAnimationSpeed :: Int -> IO () %call (int framesPerSecond) %code int result = IAnimatedMeshSceneNodeSetAnimationSpeed(framesPerSecond); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetAnimationSpeed :: IO () %call %code int result = IAnimatedMeshSceneNodeGetAnimationSpeed(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeAddShadowVolumeSceneNode :: Int -> Int -> Int -> Int -> IO () %call (int shadowMesh) (int id) (int zfailmethod) (int infinity) %code int result = IAnimatedMeshSceneNodeAddShadowVolumeSceneNode(shadowMesh, id, zfailmethod, infinity); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetJointNode :: Int -> IO () %call (int jointName) %code int result = IAnimatedMeshSceneNodeGetJointNode(jointName); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetJointNode :: Int -> IO () %call (int jointID) %code int result = IAnimatedMeshSceneNodeGetJointNode(jointID); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetJointCount :: IO () %call %code int result = IAnimatedMeshSceneNodeGetJointCount(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetMS3DJointNode :: Int -> IO () %call (int jointName) %code int result = IAnimatedMeshSceneNodeGetMS3DJointNode(jointName); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetXJointNode :: Int -> IO () %call (int jointName) %code int result = IAnimatedMeshSceneNodeGetXJointNode(jointName); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetMD2Animation :: Int -> IO () %call (int anim) %code int result = IAnimatedMeshSceneNodeSetMD2Animation(anim); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetMD2Animation :: Int -> IO () %call (int animationName) %code int result = IAnimatedMeshSceneNodeSetMD2Animation(animationName); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetFrameNr :: IO () %call %code int result = IAnimatedMeshSceneNodeGetFrameNr(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetStartFrame :: IO () %call %code int result = IAnimatedMeshSceneNodeGetStartFrame(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetEndFrame :: IO () %call %code int result = IAnimatedMeshSceneNodeGetEndFrame(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetLoopMode :: Int -> IO () %call (int playAnimationLooped) %code int result = IAnimatedMeshSceneNodeSetLoopMode(playAnimationLooped); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetAnimationEndCallback :: Int -> IO () %call (int callback) %code int result = IAnimatedMeshSceneNodeSetAnimationEndCallback(callback); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetReadOnlyMaterials :: Int -> IO () %call (int readonly) %code int result = IAnimatedMeshSceneNodeSetReadOnlyMaterials(readonly); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeIsReadOnlyMaterials :: IO () %call %code int result = IAnimatedMeshSceneNodeIsReadOnlyMaterials(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetMesh :: Int -> IO () %call (int mesh) %code int result = IAnimatedMeshSceneNodeSetMesh(mesh); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetMesh :: IO () %call %code int result = IAnimatedMeshSceneNodeGetMesh(); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeGetMD3TagTransformation :: Int -> IO () %call (int tagname) %code int result = IAnimatedMeshSceneNodeGetMD3TagTransformation(tagname); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetJointMode :: Int -> IO () %call (int mode) %code int result = IAnimatedMeshSceneNodeSetJointMode(mode); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetTransitionTime :: Int -> IO () %call (int Time) %code int result = IAnimatedMeshSceneNodeSetTransitionTime(Time); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeAnimateJoints :: Int -> IO () %call (int CalculateAbsolutePositions) %code int result = IAnimatedMeshSceneNodeAnimateJoints(CalculateAbsolutePositions); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeSetRenderFromIdentity :: Int -> IO () %call (int On) %code int result = IAnimatedMeshSceneNodeSetRenderFromIdentity(On); %fail {result < 0} {getError();} %fun IAnimatedMeshSceneNodeClone :: Int -> Int -> IO () %call (int newParent) (int newManager) %code int result = IAnimatedMeshSceneNodeClone(newParent, newManager); %fail {result < 0} {getError();} %fun IAnimationEndCallBackOnAnimationEnd :: Int -> IO () %call (int node) %code int result = IAnimationEndCallBackOnAnimationEnd(node); %fail {result < 0} {getError();} %fun IGUIColorSelectDialogIGUIColorSelectDialog :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_COLOR_SELECT_DIALOG) %code int result = IGUIColorSelectDialogIGUIColorSelectDialog(environment, parent, id, EGUIET_COLOR_SELECT_DIALOG); %fail {result < 0} {getError();} %fun IGUITableIGUITable :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_TABLE) %code int result = IGUITableIGUITable(environment, parent, id, EGUIET_TABLE); %fail {result < 0} {getError();} %fun IGUITableAddColumn :: Int -> Int -> IO () %call (int caption) (int columnIndex) %code int result = IGUITableAddColumn(caption, columnIndex); %fail {result < 0} {getError();} %fun IGUITableRemoveColumn :: Int -> IO () %call (int columnIndex) %code int result = IGUITableRemoveColumn(columnIndex); %fail {result < 0} {getError();} %fun IGUITableGetColumnCount :: IO () %call %code int result = IGUITableGetColumnCount(); %fail {result < 0} {getError();} %fun IGUITableSetActiveColumn :: Int -> Int -> IO () %call (int idx) (int doOrder) %code int result = IGUITableSetActiveColumn(idx, doOrder); %fail {result < 0} {getError();} %fun IGUITableGetActiveColumn :: IO () %call %code int result = IGUITableGetActiveColumn(); %fail {result < 0} {getError();} %fun IGUITableGetActiveColumnOrdering :: IO () %call %code int result = IGUITableGetActiveColumnOrdering(); %fail {result < 0} {getError();} %fun IGUITableSetColumnWidth :: Int -> Int -> IO () %call (int columnIndex) (int width) %code int result = IGUITableSetColumnWidth(columnIndex, width); %fail {result < 0} {getError();} %fun IGUITableSetResizableColumns :: Int -> IO () %call (int resizable) %code int result = IGUITableSetResizableColumns(resizable); %fail {result < 0} {getError();} %fun IGUITableHasResizableColumns :: IO () %call %code int result = IGUITableHasResizableColumns(); %fail {result < 0} {getError();} %fun IGUITableSetColumnOrdering :: Int -> Int -> IO () %call (int columnIndex) (int mode) %code int result = IGUITableSetColumnOrdering(columnIndex, mode); %fail {result < 0} {getError();} %fun IGUITableGetSelected :: IO () %call %code int result = IGUITableGetSelected(); %fail {result < 0} {getError();} %fun IGUITableSetSelected :: Int -> IO () %call (int index) %code int result = IGUITableSetSelected(index); %fail {result < 0} {getError();} %fun IGUITableGetRowCount :: IO () %call %code int result = IGUITableGetRowCount(); %fail {result < 0} {getError();} %fun IGUITableAddRow :: Int -> IO () %call (int rowIndex) %code int result = IGUITableAddRow(rowIndex); %fail {result < 0} {getError();} %fun IGUITableRemoveRow :: Int -> IO () %call (int rowIndex) %code int result = IGUITableRemoveRow(rowIndex); %fail {result < 0} {getError();} %fun IGUITableClearRows :: IO () %call %code int result = IGUITableClearRows(); %fail {result < 0} {getError();} %fun IGUITableSwapRows :: Int -> Int -> IO () %call (int rowIndexA) (int rowIndexB) %code int result = IGUITableSwapRows(rowIndexA, rowIndexB); %fail {result < 0} {getError();} %fun IGUITableOrderRows :: Int -> Int -> IO () %call (int columnIndex) (int mode) %code int result = IGUITableOrderRows(columnIndex, mode); %fail {result < 0} {getError();} %fun IGUITableSetCellText :: Int -> Int -> Int -> IO () %call (int rowIndex) (int columnIndex) (int text) %code int result = IGUITableSetCellText(rowIndex, columnIndex, text); %fail {result < 0} {getError();} %fun IGUITableSetCellText :: Int -> Int -> Int -> Int -> IO () %call (int rowIndex) (int columnIndex) (int text) (int color) %code int result = IGUITableSetCellText(rowIndex, columnIndex, text, color); %fail {result < 0} {getError();} %fun IGUITableSetCellData :: Int -> Int -> Int -> IO () %call (int rowIndex) (int columnIndex) (int data) %code int result = IGUITableSetCellData(rowIndex, columnIndex, data); %fail {result < 0} {getError();} %fun IGUITableSetCellColor :: Int -> Int -> Int -> IO () %call (int rowIndex) (int columnIndex) (int color) %code int result = IGUITableSetCellColor(rowIndex, columnIndex, color); %fail {result < 0} {getError();} %fun IGUITableGetCellText :: Int -> Int -> IO () %call (int rowIndex) (int columnIndex) %code int result = IGUITableGetCellText(rowIndex, columnIndex); %fail {result < 0} {getError();} %fun IGUITableGetCellData :: Int -> Int -> IO () %call (int rowIndex) (int columnIndex) %code int result = IGUITableGetCellData(rowIndex, columnIndex); %fail {result < 0} {getError();} %fun IGUITableClear :: IO () %call %code int result = IGUITableClear(); %fail {result < 0} {getError();} %fun IGUITableSetDrawFlags :: Int -> IO () %call (int flags) %code int result = IGUITableSetDrawFlags(flags); %fail {result < 0} {getError();} %fun IGUITableGetDrawFlags :: IO () %call %code int result = IGUITableGetDrawFlags(); %fail {result < 0} {getError();} %fun ISceneNodeFactoryAddSceneNode :: Int -> Int -> IO () %call (int type) (int parent) %code int result = ISceneNodeFactoryAddSceneNode(type, parent); %fail {result < 0} {getError();} %fun ISceneNodeFactoryAddSceneNode :: Int -> Int -> IO () %call (int typeName) (int parent) %code int result = ISceneNodeFactoryAddSceneNode(typeName, parent); %fail {result < 0} {getError();} %fun ISceneNodeFactoryGetCreatableSceneNodeTypeCount :: IO () %call %code int result = ISceneNodeFactoryGetCreatableSceneNodeTypeCount(); %fail {result < 0} {getError();} %fun ISceneNodeFactoryGetCreateableSceneNodeType :: Int -> IO () %call (int idx) %code int result = ISceneNodeFactoryGetCreateableSceneNodeType(idx); %fail {result < 0} {getError();} %fun ISceneNodeFactoryGetCreateableSceneNodeTypeName :: Int -> IO () %call (int idx) %code int result = ISceneNodeFactoryGetCreateableSceneNodeTypeName(idx); %fail {result < 0} {getError();} %fun ISceneNodeFactoryGetCreateableSceneNodeTypeName :: Int -> IO () %call (int type) %code int result = ISceneNodeFactoryGetCreateableSceneNodeTypeName(type); %fail {result < 0} {getError();} %fun IGUIFontDraw :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int text) (int position) (int color) (int hcenter) (int vcenter) (int clip) %code int result = IGUIFontDraw(text, position, color, hcenter, vcenter, clip); %fail {result < 0} {getError();} %fun IGUIFontGetDimension :: Int -> IO () %call (int text) %code int result = IGUIFontGetDimension(text); %fail {result < 0} {getError();} %fun IGUIFontGetCharacterFromPos :: Int -> Int -> IO () %call (int text) (int pixel_x) %code int result = IGUIFontGetCharacterFromPos(text, pixel_x); %fail {result < 0} {getError();} %fun IGUIFontGetType :: IO () %call %code int result = IGUIFontGetType(); %fail {result < 0} {getError();} %fun IGUIFontSetKerningWidth :: Int -> IO () %call (int kerning) %code int result = IGUIFontSetKerningWidth(kerning); %fail {result < 0} {getError();} %fun IGUIFontSetKerningHeight :: Int -> IO () %call (int kerning) %code int result = IGUIFontSetKerningHeight(kerning); %fail {result < 0} {getError();} %fun IGUIFontGetKerningWidth :: Int -> Int -> IO () %call (int thisLetter) (int previousLetter) %code int result = IGUIFontGetKerningWidth(thisLetter, previousLetter); %fail {result < 0} {getError();} %fun IGUIFontGetKerningHeight :: IO () %call %code int result = IGUIFontGetKerningHeight(); %fail {result < 0} {getError();} %fun IGUIFontSetInvisibleCharacters :: Int -> IO () %call (int s) %code int result = IGUIFontSetInvisibleCharacters(s); %fail {result < 0} {getError();} %fun IMeshWriterIMeshWriter :: IO () %call %code int result = IMeshWriterIMeshWriter(); %fail {result < 0} {getError();} %fun IMeshWriterGetType :: IO () %call %code int result = IMeshWriterGetType(); %fail {result < 0} {getError();} %fun IMeshWriterWriteMesh :: Int -> Int -> Int -> IO () %call (int file) (int mesh) (int flags) %code int result = IMeshWriterWriteMesh(file, mesh, flags); %fail {result < 0} {getError();} %fun IGUIElementFactoryAddGUIElement :: Int -> Int -> IO () %call (int type) (int parent) %code int result = IGUIElementFactoryAddGUIElement(type, parent); %fail {result < 0} {getError();} %fun IGUIElementFactoryAddGUIElement :: Int -> Int -> IO () %call (int typeName) (int parent) %code int result = IGUIElementFactoryAddGUIElement(typeName, parent); %fail {result < 0} {getError();} %fun IGUIElementFactoryGetCreatableGUIElementTypeCount :: IO () %call %code int result = IGUIElementFactoryGetCreatableGUIElementTypeCount(); %fail {result < 0} {getError();} %fun IGUIElementFactoryGetCreateableGUIElementType :: Int -> IO () %call (int idx) %code int result = IGUIElementFactoryGetCreateableGUIElementType(idx); %fail {result < 0} {getError();} %fun IGUIElementFactoryGetCreateableGUIElementTypeName :: Int -> IO () %call (int idx) %code int result = IGUIElementFactoryGetCreateableGUIElementTypeName(idx); %fail {result < 0} {getError();} %fun IGUIElementFactoryGetCreateableGUIElementTypeName :: Int -> IO () %call (int type) %code int result = IGUIElementFactoryGetCreateableGUIElementTypeName(type); %fail {result < 0} {getError();} %fun IShaderConstantSetCallBackOnSetMaterial :: Int -> IO () %call (int material) %code int result = IShaderConstantSetCallBackOnSetMaterial(material); %fail {result < 0} {getError();} %fun IShaderConstantSetCallBackOnSetConstants :: Int -> Int -> IO () %call (int services) (int userData) %code int result = IShaderConstantSetCallBackOnSetConstants(services, userData); %fail {result < 0} {getError();} %fun IMeshManipulatorFlipSurfaces :: Int -> IO () %call (int mesh) %code int result = IMeshManipulatorFlipSurfaces(mesh); %fail {result < 0} {getError();} %fun IMeshManipulatorSetVertexColorAlpha :: Int -> Int -> IO () %call (int mesh) (int alpha) %code int result = IMeshManipulatorSetVertexColorAlpha(mesh, alpha); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: IO () %call %code int result = IMeshManipulatorApply(); %fail {result < 0} {getError();} %fun IMeshManipulatorSetVertexColors :: Int -> Int -> IO () %call (int mesh) (int color) %code int result = IMeshManipulatorSetVertexColors(mesh, color); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: IO () %call %code int result = IMeshManipulatorApply(); %fail {result < 0} {getError();} %fun IMeshManipulatorRecalculateNormals :: Int -> Int -> Int -> IO () %call (int mesh) (int smooth) (int angleWeighted) %code int result = IMeshManipulatorRecalculateNormals(mesh, smooth, angleWeighted); %fail {result < 0} {getError();} %fun IMeshManipulatorRecalculateNormals :: Int -> Int -> Int -> IO () %call (int buffer) (int smooth) (int angleWeighted) %code int result = IMeshManipulatorRecalculateNormals(buffer, smooth, angleWeighted); %fail {result < 0} {getError();} %fun IMeshManipulatorRecalculateTangents :: Int -> Int -> Int -> Int -> IO () %call (int mesh) (int recalculateNormals) (int smooth) (int angleWeighted) %code int result = IMeshManipulatorRecalculateTangents(mesh, recalculateNormals, smooth, angleWeighted); %fail {result < 0} {getError();} %fun IMeshManipulatorScale :: Int -> Int -> IO () %call (int mesh) (int factor) %code int result = IMeshManipulatorScale(mesh, factor); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: IO () %call %code int result = IMeshManipulatorApply(); %fail {result < 0} {getError();} %fun IMeshManipulatorScale :: Int -> Int -> IO () %call (int buffer) (int factor) %code int result = IMeshManipulatorScale(buffer, factor); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: IO () %call %code int result = IMeshManipulatorApply(); %fail {result < 0} {getError();} %fun IMeshManipulatorScaleMesh :: Int -> Int -> IO () %call (int mesh) (int factor) %code int result = IMeshManipulatorScaleMesh(mesh, factor); %fail {result < 0} {getError();} %fun IMeshManipulatorScaleTCoords :: Int -> Int -> Int -> IO () %call (int mesh) (int factor) (int level) %code int result = IMeshManipulatorScaleTCoords(mesh, factor, level); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: Int -> IO () %call (int factor) %code int result = IMeshManipulatorApply(factor); %fail {result < 0} {getError();} %fun IMeshManipulatorScaleTCoords :: Int -> Int -> Int -> IO () %call (int buffer) (int factor) (int level) %code int result = IMeshManipulatorScaleTCoords(buffer, factor, level); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: Int -> IO () %call (int factor) %code int result = IMeshManipulatorApply(factor); %fail {result < 0} {getError();} %fun IMeshManipulatorTransform :: Int -> Int -> IO () %call (int mesh) (int m) %code int result = IMeshManipulatorTransform(mesh, m); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: IO () %call %code int result = IMeshManipulatorApply(); %fail {result < 0} {getError();} %fun IMeshManipulatorTransform :: Int -> Int -> IO () %call (int buffer) (int m) %code int result = IMeshManipulatorTransform(buffer, m); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: IO () %call %code int result = IMeshManipulatorApply(); %fail {result < 0} {getError();} %fun IMeshManipulatorTransformMesh :: Int -> Int -> IO () %call (int mesh) (int m) %code int result = IMeshManipulatorTransformMesh(mesh, m); %fail {result < 0} {getError();} %fun IMeshManipulatorCreateMeshCopy :: Int -> IO () %call (int mesh) %code int result = IMeshManipulatorCreateMeshCopy(mesh); %fail {result < 0} {getError();} %fun IMeshManipulatorMakePlanarTextureMapping :: Int -> Int -> IO () %call (int mesh) (int resolution) %code int result = IMeshManipulatorMakePlanarTextureMapping(mesh, resolution); %fail {result < 0} {getError();} %fun IMeshManipulatorMakePlanarTextureMapping :: Int -> Int -> IO () %call (int meshbuffer) (int resolution) %code int result = IMeshManipulatorMakePlanarTextureMapping(meshbuffer, resolution); %fail {result < 0} {getError();} %fun IMeshManipulatorMakePlanarTextureMapping :: Int -> Int -> Int -> Int -> Int -> IO () %call (int buffer) (int resolutionS) (int resolutionT) (int axis) (int offset) %code int result = IMeshManipulatorMakePlanarTextureMapping(buffer, resolutionS, resolutionT, axis, offset); %fail {result < 0} {getError();} %fun IMeshManipulatorCreateMeshWithTangents :: Int -> Int -> Int -> Int -> Int -> IO () %call (int mesh) (int recalculateNormals) (int smooth) (int angleWeighted) (int recalculateTangents) %code int result = IMeshManipulatorCreateMeshWithTangents(mesh, recalculateNormals, smooth, angleWeighted, recalculateTangents); %fail {result < 0} {getError();} %fun IMeshManipulatorCreateMeshWith2TCoords :: Int -> IO () %call (int mesh) %code int result = IMeshManipulatorCreateMeshWith2TCoords(mesh); %fail {result < 0} {getError();} %fun IMeshManipulatorCreateMeshWith1TCoords :: Int -> IO () %call (int mesh) %code int result = IMeshManipulatorCreateMeshWith1TCoords(mesh); %fail {result < 0} {getError();} %fun IMeshManipulatorCreateMeshUniquePrimitives :: Int -> IO () %call (int mesh) %code int result = IMeshManipulatorCreateMeshUniquePrimitives(mesh); %fail {result < 0} {getError();} %fun IMeshManipulatorCreateMeshWelded :: Int -> Int -> IO () %call (int mesh) (int tolerance) %code int result = IMeshManipulatorCreateMeshWelded(mesh, tolerance); %fail {result < 0} {getError();} %fun IMeshManipulatorGetPolyCount :: Int -> IO () %call (int mesh) %code int result = IMeshManipulatorGetPolyCount(mesh); %fail {result < 0} {getError();} %fun IMeshManipulatorGetPolyCount :: Int -> IO () %call (int mesh) %code int result = IMeshManipulatorGetPolyCount(mesh); %fail {result < 0} {getError();} %fun IMeshManipulatorCreateAnimatedMesh :: Int -> Int -> IO () %call (int mesh) (int type) %code int result = IMeshManipulatorCreateAnimatedMesh(mesh, type); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: Int -> Int -> Int -> IO () %call (int func) (int buffer) (int boundingBoxUpdate) %code int result = IMeshManipulatorApply(func, buffer, boundingBoxUpdate); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: Int -> Int -> Int -> IO () %call (int func) (int mesh) (int boundingBoxUpdate) %code int result = IMeshManipulatorApply(func, mesh, boundingBoxUpdate); %fail {result < 0} {getError();} %fun IMeshManipulatorGetMeshBufferCount :: IO () %call %code int result = IMeshManipulatorGetMeshBufferCount(); %fail {result < 0} {getError();} %fun IMeshManipulatorApply :: IO () %call %code int result = IMeshManipulatorApply(); %fail {result < 0} {getError();} %fun IMeshManipulatorAddInternalBox :: IO () %call %code int result = IMeshManipulatorAddInternalBox(); %fail {result < 0} {getError();} %fun SColorHSLSColorHSL :: Int -> Int -> Int -> Int -> IO () %call (int h) (int s) (int l) (int l) %code int result = SColorHSLSColorHSL(h, s, l, l); %fail {result < 0} {getError();} %fun SColorHSLFromRGB :: Int -> IO () %call (int color) %code int result = SColorHSLFromRGB(color); %fail {result < 0} {getError();} %fun SColorHSLToRGB :: Int -> IO () %call (int color) %code int result = SColorHSLToRGB(color); %fail {result < 0} {getError();} %fun SColorSColor :: IO () %call %code int result = SColorSColor(); %fail {result < 0} {getError();} %fun SColorSColor :: Int -> Int -> Int -> IO () %call (int a) (int r) (int g) %code int result = SColorSColor(a, r, g); %fail {result < 0} {getError();} %fun SColorSColor :: Int -> IO () %call (int clr) %code int result = SColorSColor(clr); %fail {result < 0} {getError();} %fun SColorGetAlpha :: IO () %call %code int result = SColorGetAlpha(); %fail {result < 0} {getError();} %fun SColorGetRed :: IO () %call %code int result = SColorGetRed(); %fail {result < 0} {getError();} %fun SColorGetGreen :: IO () %call %code int result = SColorGetGreen(); %fail {result < 0} {getError();} %fun SColorGetBlue :: IO () %call %code int result = SColorGetBlue(); %fail {result < 0} {getError();} %fun SColorGetLightness :: IO () %call %code int result = SColorGetLightness(); %fail {result < 0} {getError();} %fun SColorGetLuminance :: IO () %call %code int result = SColorGetLuminance(); %fail {result < 0} {getError();} %fun SColorGetAverage :: IO () %call %code int result = SColorGetAverage(); %fail {result < 0} {getError();} %fun SColorSetAlpha :: Int -> IO () %call (int a) %code int result = SColorSetAlpha(a); %fail {result < 0} {getError();} %fun SColorSetRed :: Int -> IO () %call (int r) %code int result = SColorSetRed(r); %fail {result < 0} {getError();} %fun SColorSetGreen :: Int -> IO () %call (int g) %code int result = SColorSetGreen(g); %fail {result < 0} {getError();} %fun SColorSetBlue :: Int -> IO () %call (int b) %code int result = SColorSetBlue(b); %fail {result < 0} {getError();} %fun SColorToA1R5G5B5 :: IO () %call %code int result = SColorToA1R5G5B5(); %fail {result < 0} {getError();} %fun SColorToOpenGLColor :: Int -> IO () %call (int dest) %code int result = SColorToOpenGLColor(dest); %fail {result < 0} {getError();} %fun SColorSet :: Int -> Int -> Int -> Int -> IO () %call (int a) (int r) (int g) (int b) %code int result = SColorSet(a, r, g, b); %fail {result < 0} {getError();} %fun SColorSet :: Int -> IO () %call (int col) %code int result = SColorSet(col); %fail {result < 0} {getError();} %fun SColorGetInterpolated :: Int -> Int -> IO () %call (int other) (int d) %code int result = SColorGetInterpolated(other, d); %fail {result < 0} {getError();} %fun SColorClamp :: IO () %call %code int result = SColorClamp(); %fail {result < 0} {getError();} %fun SColorGetInterpolated_quadratic :: Int -> Int -> Int -> IO () %call (int c1) (int c2) (int d) %code int result = SColorGetInterpolated_quadratic(c1, c2, d); %fail {result < 0} {getError();} %fun SColorClamp :: IO () %call %code int result = SColorClamp(); %fail {result < 0} {getError();} %fun SColorSetData :: Int -> Int -> IO () %call (int data) (int format) %code int result = SColorSetData(data, format); %fail {result < 0} {getError();} %fun SColorSwitch :: IO () %call %code int result = SColorSwitch(); %fail {result < 0} {getError();} %fun SColorA1R5G5B5toA8R8G8B8 :: Int -> IO () %call (int data) %code int result = SColorA1R5G5B5toA8R8G8B8(data); %fail {result < 0} {getError();} %fun SColorR5G6B5toA8R8G8B8 :: Int -> IO () %call (int data) %code int result = SColorR5G6B5toA8R8G8B8(data); %fail {result < 0} {getError();} %fun SColor_ :: IO () %call %code int result = SColor_(); %fail {result < 0} {getError();} %fun SColorSet :: IO () %call %code int result = SColorSet(); %fail {result < 0} {getError();} %fun SColorGetData :: Int -> Int -> IO () %call (int data) (int format) %code int result = SColorGetData(data, format); %fail {result < 0} {getError();} %fun SColorSwitch :: IO () %call %code int result = SColorSwitch(); %fail {result < 0} {getError();} %fun SColorA8R8G8B8toA1R5G5B5 :: IO () %call %code int result = SColorA8R8G8B8toA1R5G5B5(); %fail {result < 0} {getError();} %fun SColorA8R8G8B8toR5G6B5 :: IO () %call %code int result = SColorA8R8G8B8toR5G6B5(); %fail {result < 0} {getError();} %fun SColorfSColorf :: IO () %call %code int result = SColorfSColorf(); %fail {result < 0} {getError();} %fun SColorfSColorf :: Int -> Int -> Int -> Int -> Int -> IO () %call (int r) (int g) (int b) (int a) (int a) %code int result = SColorfSColorf(r, g, b, a, a); %fail {result < 0} {getError();} %fun SColorfSColorf :: Int -> IO () %call (int c) %code int result = SColorfSColorf(c); %fail {result < 0} {getError();} %fun SColorfGetRed :: IO () %call %code int result = SColorfGetRed(); %fail {result < 0} {getError();} %fun SColorfGetGreen :: IO () %call %code int result = SColorfGetGreen(); %fail {result < 0} {getError();} %fun SColorfGetBlue :: IO () %call %code int result = SColorfGetBlue(); %fail {result < 0} {getError();} %fun SColorfGetAlpha :: IO () %call %code int result = SColorfGetAlpha(); %fail {result < 0} {getError();} %fun SColorfToSColor :: IO () %call %code int result = SColorfToSColor(); %fail {result < 0} {getError();} %fun SColorfSet :: Int -> Int -> Int -> IO () %call (int rr) (int gg) (int bb) %code int result = SColorfSet(rr, gg, bb); %fail {result < 0} {getError();} %fun SColorfSet :: Int -> Int -> Int -> Int -> IO () %call (int aa) (int rr) (int gg) (int bb) %code int result = SColorfSet(aa, rr, gg, bb); %fail {result < 0} {getError();} %fun SColorfGetInterpolated :: Int -> Int -> IO () %call (int other) (int d) %code int result = SColorfGetInterpolated(other, d); %fail {result < 0} {getError();} %fun SColorfClamp :: IO () %call %code int result = SColorfClamp(); %fail {result < 0} {getError();} %fun SColorfGetInterpolated_quadratic :: Int -> Int -> Int -> IO () %call (int c1) (int c2) (int d) %code int result = SColorfGetInterpolated_quadratic(c1, c2, d); %fail {result < 0} {getError();} %fun SColorfClamp :: IO () %call %code int result = SColorfClamp(); %fail {result < 0} {getError();} %fun SColorfSetColorComponentValue :: Int -> Int -> IO () %call (int index) (int value) %code int result = SColorfSetColorComponentValue(index, value); %fail {result < 0} {getError();} %fun SColorfSwitch :: IO () %call %code int result = SColorfSwitch(); %fail {result < 0} {getError();} %fun SColorfGetAlpha :: IO () %call %code int result = SColorfGetAlpha(); %fail {result < 0} {getError();} %fun SColorfGetRed :: IO () %call %code int result = SColorfGetRed(); %fail {result < 0} {getError();} %fun SColorfGetGreen :: IO () %call %code int result = SColorfGetGreen(); %fail {result < 0} {getError();} %fun SColorfGetBlue :: IO () %call %code int result = SColorfGetBlue(); %fail {result < 0} {getError();} %fun IImageLoaderIsALoadableFileExtension :: Int -> IO () %call (int filename) %code int result = IImageLoaderIsALoadableFileExtension(filename); %fail {result < 0} {getError();} %fun IImageLoaderIsALoadableFileFormat :: Int -> IO () %call (int file) %code int result = IImageLoaderIsALoadableFileFormat(file); %fail {result < 0} {getError();} %fun IImageLoaderLoadImage :: Int -> IO () %call (int file) %code int result = IImageLoaderLoadImage(file); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorAnimateNode :: Int -> Int -> IO () %call (int node) (int timeMs) %code int result = ISceneNodeAnimatorAnimateNode(node, timeMs); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorCreateClone :: Int -> Int -> IO () %call (int node) (int newManager) %code int result = ISceneNodeAnimatorCreateClone(node, newManager); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorIsEventReceiverEnabled :: IO () %call %code int result = ISceneNodeAnimatorIsEventReceiverEnabled(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorOnEvent :: Int -> IO () %call (int event) %code int result = ISceneNodeAnimatorOnEvent(event); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorGetType :: IO () %call %code int result = ISceneNodeAnimatorGetType(); %fail {result < 0} {getError();} %fun ISceneNodeAnimatorHasFinished :: IO () %call %code int result = ISceneNodeAnimatorHasFinished(); %fail {result < 0} {getError();} %fun IOSOperatorIOSOperator :: IO () %call %code int result = IOSOperatorIOSOperator(); %fail {result < 0} {getError();} %fun IOSOperatorGetOperationSystemVersion :: IO () %call %code int result = IOSOperatorGetOperationSystemVersion(); %fail {result < 0} {getError();} %fun IOSOperatorCopyToClipboard :: Int -> IO () %call (int text) %code int result = IOSOperatorCopyToClipboard(text); %fail {result < 0} {getError();} %fun IOSOperatorGetTextFromClipboard :: IO () %call %code int result = IOSOperatorGetTextFromClipboard(); %fail {result < 0} {getError();} %fun IOSOperatorGetProcessorSpeedMHz :: Int -> IO () %call (int MHz) %code int result = IOSOperatorGetProcessorSpeedMHz(MHz); %fail {result < 0} {getError();} %fun IOSOperatorGetSystemMemory :: Int -> Int -> IO () %call (int Total) (int Avail) %code int result = IOSOperatorGetSystemMemory(Total, Avail); %fail {result < 0} {getError();} %fun IQ3LevelMeshGetShader :: Int -> Int -> IO () %call (int filename) (int fileNameIsValid) %code int result = IQ3LevelMeshGetShader(filename, fileNameIsValid); %fail {result < 0} {getError();} %fun IQ3LevelMeshGetShader :: Int -> IO () %call (int index) %code int result = IQ3LevelMeshGetShader(index); %fail {result < 0} {getError();} %fun IQ3LevelMeshGetEntityList :: IO () %call %code int result = IQ3LevelMeshGetEntityList(); %fail {result < 0} {getError();} %fun ILightManagerOnPreRender :: Int -> IO () %call (int lightList) %code int result = ILightManagerOnPreRender(lightList); %fail {result < 0} {getError();} %fun ILightManagerOnPostRender :: IO () %call %code int result = ILightManagerOnPostRender(); %fail {result < 0} {getError();} %fun ILightManagerOnRenderPassPreRender :: Int -> IO () %call (int renderPass) %code int result = ILightManagerOnRenderPassPreRender(renderPass); %fail {result < 0} {getError();} %fun ILightManagerOnRenderPassPostRender :: Int -> IO () %call (int renderPass) %code int result = ILightManagerOnRenderPassPostRender(renderPass); %fail {result < 0} {getError();} %fun ILightManagerOnNodePreRender :: Int -> IO () %call (int node) %code int result = ILightManagerOnNodePreRender(node); %fail {result < 0} {getError();} %fun ILightManagerOnNodePostRender :: Int -> IO () %call (int node) %code int result = ILightManagerOnNodePostRender(node); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorSetPoint :: Int -> IO () %call (int point) %code int result = IParticleAttractionAffectorSetPoint(point); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorSetAttract :: Int -> IO () %call (int attract) %code int result = IParticleAttractionAffectorSetAttract(attract); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorSetAffectX :: Int -> IO () %call (int affect) %code int result = IParticleAttractionAffectorSetAffectX(affect); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorSetAffectY :: Int -> IO () %call (int affect) %code int result = IParticleAttractionAffectorSetAffectY(affect); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorSetAffectZ :: Int -> IO () %call (int affect) %code int result = IParticleAttractionAffectorSetAffectZ(affect); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorGetPoint :: IO () %call %code int result = IParticleAttractionAffectorGetPoint(); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorGetAttract :: IO () %call %code int result = IParticleAttractionAffectorGetAttract(); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorGetAffectX :: IO () %call %code int result = IParticleAttractionAffectorGetAffectX(); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorGetAffectY :: IO () %call %code int result = IParticleAttractionAffectorGetAffectY(); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorGetAffectZ :: IO () %call %code int result = IParticleAttractionAffectorGetAffectZ(); %fail {result < 0} {getError();} %fun IParticleAttractionAffectorGetType :: IO () %call %code int result = IParticleAttractionAffectorGetType(); %fail {result < 0} {getError();} %fun ILightSceneNodeILightSceneNode :: Int -> Int -> Int -> Int -> Int -> IO () %call (int parent) (int mgr) (int id) (int position) (int parent) %code int result = ILightSceneNodeILightSceneNode(parent, mgr, id, position, parent); %fail {result < 0} {getError();} %fun ILightSceneNodeSetLightData :: Int -> IO () %call (int light) %code int result = ILightSceneNodeSetLightData(light); %fail {result < 0} {getError();} %fun ILightSceneNodeGetLightData :: IO () %call %code int result = ILightSceneNodeGetLightData(); %fail {result < 0} {getError();} %fun ILightSceneNodeGetLightData :: IO () %call %code int result = ILightSceneNodeGetLightData(); %fail {result < 0} {getError();} %fun ILightSceneNodeSetVisible :: Int -> IO () %call (int isVisible) %code int result = ILightSceneNodeSetVisible(isVisible); %fail {result < 0} {getError();} %fun ILightSceneNodeSetRadius :: Int -> IO () %call (int radius) %code int result = ILightSceneNodeSetRadius(radius); %fail {result < 0} {getError();} %fun ILightSceneNodeGetRadius :: IO () %call %code int result = ILightSceneNodeGetRadius(); %fail {result < 0} {getError();} %fun ILightSceneNodeSetLightType :: Int -> IO () %call (int type) %code int result = ILightSceneNodeSetLightType(type); %fail {result < 0} {getError();} %fun ILightSceneNodeGetLightType :: IO () %call %code int result = ILightSceneNodeGetLightType(); %fail {result < 0} {getError();} %fun ILightSceneNodeEnableCastShadow :: Int -> IO () %call (int shadow) %code int result = ILightSceneNodeEnableCastShadow(shadow); %fail {result < 0} {getError();} %fun ILightSceneNodeGetCastShadow :: IO () %call %code int result = ILightSceneNodeGetCastShadow(); %fail {result < 0} {getError();} %fun IGUIComboBoxIGUIComboBox :: Int -> Int -> Int -> Int -> IO () %call (int environment) (int parent) (int id) (int EGUIET_COMBO_BOX) %code int result = IGUIComboBoxIGUIComboBox(environment, parent, id, EGUIET_COMBO_BOX); %fail {result < 0} {getError();} %fun IGUIComboBoxGetItemCount :: IO () %call %code int result = IGUIComboBoxGetItemCount(); %fail {result < 0} {getError();} %fun IGUIComboBoxGetItem :: Int -> IO () %call (int idx) %code int result = IGUIComboBoxGetItem(idx); %fail {result < 0} {getError();} %fun IGUIComboBoxGetItemData :: Int -> IO () %call (int idx) %code int result = IGUIComboBoxGetItemData(idx); %fail {result < 0} {getError();} %fun IGUIComboBoxGetIndexForItemData :: Int -> IO () %call (int data) %code int result = IGUIComboBoxGetIndexForItemData(data); %fail {result < 0} {getError();} %fun IGUIComboBoxAddItem :: Int -> Int -> IO () %call (int text) (int data) %code int result = IGUIComboBoxAddItem(text, data); %fail {result < 0} {getError();} %fun IGUIComboBoxRemoveItem :: Int -> IO () %call (int idx) %code int result = IGUIComboBoxRemoveItem(idx); %fail {result < 0} {getError();} %fun IGUIComboBoxClear :: IO () %call %code int result = IGUIComboBoxClear(); %fail {result < 0} {getError();} %fun IGUIComboBoxGetSelected :: IO () %call %code int result = IGUIComboBoxGetSelected(); %fail {result < 0} {getError();} %fun IGUIComboBoxSetSelected :: Int -> IO () %call (int idx) %code int result = IGUIComboBoxSetSelected(idx); %fail {result < 0} {getError();} %fun IGUIComboBoxSetTextAlignment :: Int -> Int -> IO () %call (int horizontal) (int vertical) %code int result = IGUIComboBoxSetTextAlignment(horizontal, vertical); %fail {result < 0} {getError();} %fun IGUIElementIGUIElement :: Int -> Int -> Int -> Int -> Int -> IO () %call (int type) (int environment) (int parent) (int id) (int type) %code int result = IGUIElementIGUIElement(type, environment, parent, id, type); %fail {result < 0} {getError();} %fun IGUIElementSetDebugName :: IO () %call %code int result = IGUIElementSetDebugName(); %fail {result < 0} {getError();} %fun IGUIElementAddChildToEnd :: IO () %call %code int result = IGUIElementAddChildToEnd(); %fail {result < 0} {getError();} %fun IGUIElementRecalculateAbsolutePosition :: IO () %call %code int result = IGUIElementRecalculateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementIGUIElement :: IO () %call %code int result = IGUIElementIGUIElement(); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementEnd :: IO () %call %code int result = IGUIElementEnd(); %fail {result < 0} {getError();} %fun IGUIElementGetParent :: IO () %call %code int result = IGUIElementGetParent(); %fail {result < 0} {getError();} %fun IGUIElementGetRelativePosition :: IO () %call %code int result = IGUIElementGetRelativePosition(); %fail {result < 0} {getError();} %fun IGUIElementSetRelativePosition :: Int -> IO () %call (int r) %code int result = IGUIElementSetRelativePosition(r); %fail {result < 0} {getError();} %fun IGUIElementGetAbsolutePosition :: IO () %call %code int result = IGUIElementGetAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementD :: IO () %call %code int result = IGUIElementD(); %fail {result < 0} {getError();} %fun IGUIElementUpdateAbsolutePosition :: IO () %call %code int result = IGUIElementUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementSetRelativePosition :: Int -> IO () %call (int position) %code int result = IGUIElementSetRelativePosition(position); %fail {result < 0} {getError();} %fun IGUIElementGetSize :: IO () %call %code int result = IGUIElementGetSize(); %fail {result < 0} {getError();} %fun IGUIElementRectangle :: Int -> Int -> Int -> Int -> IO () %call (int X) (int Y) (int Width) (int Height) %code int result = IGUIElementRectangle(X, Y, Width, Height); %fail {result < 0} {getError();} %fun IGUIElementSetRelativePosition :: IO () %call %code int result = IGUIElementSetRelativePosition(); %fail {result < 0} {getError();} %fun IGUIElementSetRelativePositionProportional :: Int -> IO () %call (int r) %code int result = IGUIElementSetRelativePositionProportional(r); %fail {result < 0} {getError();} %fun IGUIElementGetAbsolutePosition :: IO () %call %code int result = IGUIElementGetAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementUpdateAbsolutePosition :: IO () %call %code int result = IGUIElementUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementGetAbsolutePosition :: IO () %call %code int result = IGUIElementGetAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementGetAbsoluteClippingRect :: IO () %call %code int result = IGUIElementGetAbsoluteClippingRect(); %fail {result < 0} {getError();} %fun IGUIElementSetNotClipped :: Int -> IO () %call (int noClip) %code int result = IGUIElementSetNotClipped(noClip); %fail {result < 0} {getError();} %fun IGUIElementUpdateAbsolutePosition :: IO () %call %code int result = IGUIElementUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementIsNotClipped :: IO () %call %code int result = IGUIElementIsNotClipped(); %fail {result < 0} {getError();} %fun IGUIElementSetMaxSize :: Int -> IO () %call (int size) %code int result = IGUIElementSetMaxSize(size); %fail {result < 0} {getError();} %fun IGUIElementUpdateAbsolutePosition :: IO () %call %code int result = IGUIElementUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementSetMinSize :: Int -> IO () %call (int size) %code int result = IGUIElementSetMinSize(size); %fail {result < 0} {getError();} %fun IGUIElementUpdateAbsolutePosition :: IO () %call %code int result = IGUIElementUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementSetAlignment :: Int -> Int -> Int -> Int -> IO () %call (int left) (int right) (int top) (int bottom) %code int result = IGUIElementSetAlignment(left, right, top, bottom); %fail {result < 0} {getError();} %fun IGUIElementR :: IO () %call %code int result = IGUIElementR(); %fail {result < 0} {getError();} %fun IGUIElementD :: Int -> Int -> IO () %call (int Width) (int Height) %code int result = IGUIElementD(Width, Height); %fail {result < 0} {getError();} %fun IGUIElementUpdateAbsolutePosition :: IO () %call %code int result = IGUIElementUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementRecalculateAbsolutePosition :: IO () %call %code int result = IGUIElementRecalculateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementEnd :: IO () %call %code int result = IGUIElementEnd(); %fail {result < 0} {getError();} %fun IGUIElementGetElementFromPoint :: Int -> IO () %call (int point) %code int result = IGUIElementGetElementFromPoint(point); %fail {result < 0} {getError();} %fun IGUIElementGetLast :: IO () %call %code int result = IGUIElementGetLast(); %fail {result < 0} {getError();} %fun IGUIElementWhile :: Int -> IO () %call (int it) %code int result = IGUIElementWhile(it); %fail {result < 0} {getError();} %fun IGUIElementIsPointInside :: Int -> IO () %call (int point) %code int result = IGUIElementIsPointInside(point); %fail {result < 0} {getError();} %fun IGUIElementAddChild :: Int -> IO () %call (int child) %code int result = IGUIElementAddChild(child); %fail {result < 0} {getError();} %fun IGUIElementAddChildToEnd :: IO () %call %code int result = IGUIElementAddChildToEnd(); %fail {result < 0} {getError();} %fun IGUIElementUpdateAbsolutePosition :: IO () %call %code int result = IGUIElementUpdateAbsolutePosition(); %fail {result < 0} {getError();} %fun IGUIElementRemoveChild :: Int -> IO () %call (int child) %code int result = IGUIElementRemoveChild(child); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementEnd :: IO () %call %code int result = IGUIElementEnd(); %fail {result < 0} {getError();} %fun IGUIElementErase :: IO () %call %code int result = IGUIElementErase(); %fail {result < 0} {getError();} %fun IGUIElementRemove :: IO () %call %code int result = IGUIElementRemove(); %fail {result < 0} {getError();} %fun IGUIElementDraw :: IO () %call %code int result = IGUIElementDraw(); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementEnd :: IO () %call %code int result = IGUIElementEnd(); %fail {result < 0} {getError();} %fun IGUIElementOnPostRender :: Int -> IO () %call (int timeMs) %code int result = IGUIElementOnPostRender(timeMs); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementEnd :: IO () %call %code int result = IGUIElementEnd(); %fail {result < 0} {getError();} %fun IGUIElementMove :: Int -> IO () %call (int absoluteMovement) %code int result = IGUIElementMove(absoluteMovement); %fail {result < 0} {getError();} %fun IGUIElementSetRelativePosition :: Int -> IO () %call (int absoluteMovement) %code int result = IGUIElementSetRelativePosition(absoluteMovement); %fail {result < 0} {getError();} %fun IGUIElementIsVisible :: IO () %call %code int result = IGUIElementIsVisible(); %fail {result < 0} {getError();} %fun IGUIElementSetVisible :: Int -> IO () %call (int visible) %code int result = IGUIElementSetVisible(visible); %fail {result < 0} {getError();} %fun IGUIElementIsSubElement :: IO () %call %code int result = IGUIElementIsSubElement(); %fail {result < 0} {getError();} %fun IGUIElementSetSubElement :: Int -> IO () %call (int subElement) %code int result = IGUIElementSetSubElement(subElement); %fail {result < 0} {getError();} %fun IGUIElementSetTabStop :: Int -> IO () %call (int enable) %code int result = IGUIElementSetTabStop(enable); %fail {result < 0} {getError();} %fun IGUIElementIsTabStop :: IO () %call %code int result = IGUIElementIsTabStop(); %fail {result < 0} {getError();} %fun IGUIElementSetTabOrder :: Int -> IO () %call (int index) %code int result = IGUIElementSetTabOrder(index); %fail {result < 0} {getError();} %fun IGUIElementGetTabGroup :: IO () %call %code int result = IGUIElementGetTabGroup(); %fail {result < 0} {getError();} %fun IGUIElementWhile :: Int -> IO () %call (int _Parent) %code int result = IGUIElementWhile(_Parent); %fail {result < 0} {getError();} %fun IGUIElementGetNextElement :: IO () %call %code int result = IGUIElementGetNextElement(); %fail {result < 0} {getError();} %fun IGUIElementGetTabOrder :: IO () %call %code int result = IGUIElementGetTabOrder(); %fail {result < 0} {getError();} %fun IGUIElementGetTabOrder :: IO () %call %code int result = IGUIElementGetTabOrder(); %fail {result < 0} {getError();} %fun IGUIElementSetTabGroup :: Int -> IO () %call (int isGroup) %code int result = IGUIElementSetTabGroup(isGroup); %fail {result < 0} {getError();} %fun IGUIElementIsTabGroup :: IO () %call %code int result = IGUIElementIsTabGroup(); %fail {result < 0} {getError();} %fun IGUIElementGetTabGroup :: IO () %call %code int result = IGUIElementGetTabGroup(); %fail {result < 0} {getError();} %fun IGUIElementWhile :: Int -> IO () %call (int ret) %code int result = IGUIElementWhile(ret); %fail {result < 0} {getError();} %fun IGUIElementIsEnabled :: IO () %call %code int result = IGUIElementIsEnabled(); %fail {result < 0} {getError();} %fun IGUIElementSetEnabled :: Int -> IO () %call (int enabled) %code int result = IGUIElementSetEnabled(enabled); %fail {result < 0} {getError();} %fun IGUIElementSetText :: Int -> IO () %call (int text) %code int result = IGUIElementSetText(text); %fail {result < 0} {getError();} %fun IGUIElementGetText :: IO () %call %code int result = IGUIElementGetText(); %fail {result < 0} {getError();} %fun IGUIElementSetToolTipText :: Int -> IO () %call (int text) %code int result = IGUIElementSetToolTipText(text); %fail {result < 0} {getError();} %fun IGUIElementGetToolTipText :: IO () %call %code int result = IGUIElementGetToolTipText(); %fail {result < 0} {getError();} %fun IGUIElementGetID :: IO () %call %code int result = IGUIElementGetID(); %fail {result < 0} {getError();} %fun IGUIElementSetID :: Int -> IO () %call (int id) %code int result = IGUIElementSetID(id); %fail {result < 0} {getError();} %fun IGUIElementOnEvent :: Int -> IO () %call (int event) %code int result = IGUIElementOnEvent(event); %fail {result < 0} {getError();} %fun IGUIElementBringToFront :: Int -> IO () %call (int element) %code int result = IGUIElementBringToFront(element); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementEnd :: IO () %call %code int result = IGUIElementEnd(); %fail {result < 0} {getError();} %fun IGUIElementErase :: IO () %call %code int result = IGUIElementErase(); %fail {result < 0} {getError();} %fun IGUIElementPush_back :: IO () %call %code int result = IGUIElementPush_back(); %fail {result < 0} {getError();} %fun IGUIElementGetChildren :: IO () %call %code int result = IGUIElementGetChildren(); %fail {result < 0} {getError();} %fun IGUIElementGetElementFromId :: Int -> Int -> IO () %call (int id) (int searchchildren) %code int result = IGUIElementGetElementFromId(id, searchchildren); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementEnd :: IO () %call %code int result = IGUIElementEnd(); %fail {result < 0} {getError();} %fun IGUIElementIsMyChild :: Int -> IO () %call (int child) %code int result = IGUIElementIsMyChild(child); %fail {result < 0} {getError();} %fun IGUIElementWhile :: Int -> IO () %call (int child) %code int result = IGUIElementWhile(child); %fail {result < 0} {getError();} %fun IGUIElementGetNextElement :: Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int startOrder) (int reverse) (int group) (int first) (int closest) (int includeInvisible) %code int result = IGUIElementGetNextElement(startOrder, reverse, group, first, closest, includeInvisible); %fail {result < 0} {getError();} %fun IGUIElementBegin :: IO () %call %code int result = IGUIElementBegin(); %fail {result < 0} {getError();} %fun IGUIElementWhile :: Int -> IO () %call (int it) %code int result = IGUIElementWhile(it); %fail {result < 0} {getError();} %fun IGUIElementGetTabOrder :: IO () %call %code int result = IGUIElementGetTabOrder(); %fail {result < 0} {getError();} %fun IGUIElementGetTabOrder :: IO () %call %code int result = IGUIElementGetTabOrder(); %fail {result < 0} {getError();} %fun IGUIElementGetType :: IO () %call %code int result = IGUIElementGetType(); %fail {result < 0} {getError();} %fun IGUIElementHasType :: Int -> IO () %call (int type) %code int result = IGUIElementHasType(type); %fail {result < 0} {getError();} %fun IGUIElementGetTypeName :: IO () %call %code int result = IGUIElementGetTypeName(); %fail {result < 0} {getError();} %fun IGUIElementSerializeAttributes :: Int -> Int -> IO () %call (int out) (int options) %code int result = IGUIElementSerializeAttributes(out, options); %fail {result < 0} {getError();} %fun IGUIElementAddInt :: IO () %call %code int result = IGUIElementAddInt(); %fail {result < 0} {getError();} %fun IGUIElementAddString :: IO () %call %code int result = IGUIElementAddString(); %fail {result < 0} {getError();} %fun IGUIElementAddRect :: IO () %call %code int result = IGUIElementAddRect(); %fail {result < 0} {getError();} %fun IGUIElementAddPosition2d :: Int -> IO () %call (int Width) %code int result = IGUIElementAddPosition2d(Width); %fail {result < 0} {getError();} %fun IGUIElementAddPosition2d :: Int -> IO () %call (int Width) %code int result = IGUIElementAddPosition2d(Width); %fail {result < 0} {getError();} %fun IGUIElementAddEnum :: IO () %call %code int result = IGUIElementAddEnum(); %fail {result < 0} {getError();} %fun IGUIElementAddEnum :: IO () %call %code int result = IGUIElementAddEnum(); %fail {result < 0} {getError();} %fun IGUIElementAddEnum :: IO () %call %code int result = IGUIElementAddEnum(); %fail {result < 0} {getError();} %fun IGUIElementAddEnum :: IO () %call %code int result = IGUIElementAddEnum(); %fail {result < 0} {getError();} %fun IGUIElementAddBool :: IO () %call %code int result = IGUIElementAddBool(); %fail {result < 0} {getError();} %fun IGUIElementAddBool :: IO () %call %code int result = IGUIElementAddBool(); %fail {result < 0} {getError();} %fun IGUIElementAddBool :: IO () %call %code int result = IGUIElementAddBool(); %fail {result < 0} {getError();} %fun IGUIElementAddBool :: IO () %call %code int result = IGUIElementAddBool(); %fail {result < 0} {getError();} %fun IGUIElementAddInt :: IO () %call %code int result = IGUIElementAddInt(); %fail {result < 0} {getError();} %fun IGUIElementAddBool :: IO () %call %code int result = IGUIElementAddBool(); %fail {result < 0} {getError();} %fun IGUIElementDeserializeAttributes :: Int -> Int -> IO () %call (int i_n) (int options) %code int result = IGUIElementDeserializeAttributes(i_n, options); %fail {result < 0} {getError();} %fun IGUIElementSetID :: IO () %call %code int result = IGUIElementSetID(); %fail {result < 0} {getError();} %fun IGUIElementSetText :: IO () %call %code int result = IGUIElementSetText(); %fail {result < 0} {getError();} %fun IGUIElementSetVisible :: IO () %call %code int result = IGUIElementSetVisible(); %fail {result < 0} {getError();} %fun IGUIElementSetEnabled :: IO () %call %code int result = IGUIElementSetEnabled(); %fail {result < 0} {getError();} %fun IGUIElementGetAttributeAsBool :: IO () %call %code int result = IGUIElementGetAttributeAsBool(); %fail {result < 0} {getError();} %fun IGUIElementGetAttributeAsBool :: IO () %call %code int result = IGUIElementGetAttributeAsBool(); %fail {result < 0} {getError();} %fun IGUIElementGetAttributeAsInt :: IO () %call %code int result = IGUIElementGetAttributeAsInt(); %fail {result < 0} {getError();} %fun IGUIElementGetAttributeAsPosition2d :: IO () %call %code int result = IGUIElementGetAttributeAsPosition2d(); %fail {result < 0} {getError();} %fun IGUIElementSetMaxSize :: Int -> IO () %call (int X) %code int result = IGUIElementSetMaxSize(X); %fail {result < 0} {getError();} %fun IGUIElementGetAttributeAsPosition2d :: IO () %call %code int result = IGUIElementGetAttributeAsPosition2d(); %fail {result < 0} {getError();} %fun IGUIElementSetMinSize :: Int -> IO () %call (int X) %code int result = IGUIElementSetMinSize(X); %fail {result < 0} {getError();} %fun IGUIElementSetAlignment :: Int -> Int -> Int -> Int -> IO () %call (int LeftAlign) (int RightAlign) (int TopAlign) (int BottomAlign) %code int result = IGUIElementSetAlignment(LeftAlign, RightAlign, TopAlign, BottomAlign); %fail {result < 0} {getError();} %fun IGUIElementSetRelativePosition :: IO () %call %code int result = IGUIElementSetRelativePosition(); %fail {result < 0} {getError();} %fun IGUIElementSetNotClipped :: IO () %call %code int result = IGUIElementSetNotClipped(); %fail {result < 0} {getError();} %fun IAttributesGetAttributeCount :: IO () %call %code int result = IAttributesGetAttributeCount(); %fail {result < 0} {getError();} %fun IAttributesGetAttributeName :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeName(index); %fail {result < 0} {getError();} %fun IAttributesGetAttributeType :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeType(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeType :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeType(index); %fail {result < 0} {getError();} %fun IAttributesGetAttributeTypeString :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeTypeString(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeTypeString :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeTypeString(index); %fail {result < 0} {getError();} %fun IAttributesExistsAttribute :: Int -> IO () %call (int attributeName) %code int result = IAttributesExistsAttribute(attributeName); %fail {result < 0} {getError();} %fun IAttributesFindAttribute :: Int -> IO () %call (int attributeName) %code int result = IAttributesFindAttribute(attributeName); %fail {result < 0} {getError();} %fun IAttributesClear :: IO () %call %code int result = IAttributesClear(); %fail {result < 0} {getError();} %fun IAttributesRead :: Int -> Int -> Int -> IO () %call (int reader) (int readCurrentElementOnly) (int elementName) %code int result = IAttributesRead(reader, readCurrentElementOnly, elementName); %fail {result < 0} {getError();} %fun IAttributesWrite :: Int -> Int -> Int -> IO () %call (int writer) (int writeXMLHeader) (int elementName) %code int result = IAttributesWrite(writer, writeXMLHeader, elementName); %fail {result < 0} {getError();} %fun IAttributesAddInt :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddInt(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesSetAttribute(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsInt :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsInt(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsInt :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsInt(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int value) %code int result = IAttributesSetAttribute(index, value); %fail {result < 0} {getError();} %fun IAttributesAddFloat :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddFloat(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesSetAttribute(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsFloat :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsFloat(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsFloat :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsFloat(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int value) %code int result = IAttributesSetAttribute(index, value); %fail {result < 0} {getError();} %fun IAttributesAddString :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddString(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesSetAttribute(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsString :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsString(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsString :: Int -> Int -> IO () %call (int attributeName) (int target) %code int result = IAttributesGetAttributeAsString(attributeName, target); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsString :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsString(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int value) %code int result = IAttributesSetAttribute(index, value); %fail {result < 0} {getError();} %fun IAttributesAddString :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddString(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesSetAttribute(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsStringW :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsStringW(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsStringW :: Int -> Int -> IO () %call (int attributeName) (int target) %code int result = IAttributesGetAttributeAsStringW(attributeName, target); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsStringW :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsStringW(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int value) %code int result = IAttributesSetAttribute(index, value); %fail {result < 0} {getError();} %fun IAttributesAddBinary :: Int -> Int -> Int -> IO () %call (int attributeName) (int data) (int dataSizeInBytes) %code int result = IAttributesAddBinary(attributeName, data, dataSizeInBytes); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> Int -> IO () %call (int attributeName) (int data) (int dataSizeInBytes) %code int result = IAttributesSetAttribute(attributeName, data, dataSizeInBytes); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsBinaryData :: Int -> Int -> Int -> IO () %call (int attributeName) (int outData) (int maxSizeInBytes) %code int result = IAttributesGetAttributeAsBinaryData(attributeName, outData, maxSizeInBytes); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsBinaryData :: Int -> Int -> Int -> IO () %call (int index) (int outData) (int maxSizeInBytes) %code int result = IAttributesGetAttributeAsBinaryData(index, outData, maxSizeInBytes); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> Int -> IO () %call (int index) (int data) (int dataSizeInBytes) %code int result = IAttributesSetAttribute(index, data, dataSizeInBytes); %fail {result < 0} {getError();} %fun IAttributesAddArray :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddArray(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesSetAttribute(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsArray :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsArray(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsArray :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsArray(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int value) %code int result = IAttributesSetAttribute(index, value); %fail {result < 0} {getError();} %fun IAttributesAddBool :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddBool(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesSetAttribute(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsBool :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsBool(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsBool :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsBool(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int value) %code int result = IAttributesSetAttribute(index, value); %fail {result < 0} {getError();} %fun IAttributesAddEnum :: Int -> Int -> Int -> IO () %call (int attributeName) (int enumValue) (int enumerationLiterals) %code int result = IAttributesAddEnum(attributeName, enumValue, enumerationLiterals); %fail {result < 0} {getError();} %fun IAttributesAddEnum :: Int -> Int -> Int -> IO () %call (int attributeName) (int enumValue) (int enumerationLiterals) %code int result = IAttributesAddEnum(attributeName, enumValue, enumerationLiterals); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> Int -> IO () %call (int attributeName) (int enumValue) (int enumerationLiterals) %code int result = IAttributesSetAttribute(attributeName, enumValue, enumerationLiterals); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsEnumeration :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsEnumeration(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsEnumeration :: Int -> Int -> IO () %call (int attributeName) (int enumerationLiteralsToUse) %code int result = IAttributesGetAttributeAsEnumeration(attributeName, enumerationLiteralsToUse); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsEnumeration :: Int -> Int -> IO () %call (int index) (int enumerationLiteralsToUse) %code int result = IAttributesGetAttributeAsEnumeration(index, enumerationLiteralsToUse); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsEnumeration :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsEnumeration(index); %fail {result < 0} {getError();} %fun IAttributesGetAttributeEnumerationLiteralsOfEnumeration :: Int -> Int -> IO () %call (int attributeName) (int outLiterals) %code int result = IAttributesGetAttributeEnumerationLiteralsOfEnumeration(attributeName, outLiterals); %fail {result < 0} {getError();} %fun IAttributesGetAttributeEnumerationLiteralsOfEnumeration :: Int -> Int -> IO () %call (int index) (int outLiterals) %code int result = IAttributesGetAttributeEnumerationLiteralsOfEnumeration(index, outLiterals); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> Int -> IO () %call (int index) (int enumValue) (int enumerationLiterals) %code int result = IAttributesSetAttribute(index, enumValue, enumerationLiterals); %fail {result < 0} {getError();} %fun IAttributesAddColor :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddColor(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int color) %code int result = IAttributesSetAttribute(attributeName, color); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsColor :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsColor(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsColor :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsColor(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int color) %code int result = IAttributesSetAttribute(index, color); %fail {result < 0} {getError();} %fun IAttributesAddColorf :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddColorf(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int color) %code int result = IAttributesSetAttribute(attributeName, color); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsColorf :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsColorf(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsColorf :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsColorf(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int color) %code int result = IAttributesSetAttribute(index, color); %fail {result < 0} {getError();} %fun IAttributesAddVector3d :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddVector3d(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsVector3d :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsVector3d(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsVector3d :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsVector3d(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddPosition2d :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddPosition2d(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsPosition2d :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsPosition2d(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsPosition2d :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsPosition2d(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddRect :: Int -> Int -> IO () %call (int attributeName) (int value) %code int result = IAttributesAddRect(attributeName, value); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsRect :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsRect(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsRect :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsRect(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddMatrix :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesAddMatrix(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsMatrix :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsMatrix(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsMatrix :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsMatrix(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddQuaternion :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesAddQuaternion(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsQuaternion :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsQuaternion(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsQuaternion :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsQuaternion(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddBox3d :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesAddBox3d(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsBox3d :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsBox3d(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsBox3d :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsBox3d(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddPlane3d :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesAddPlane3d(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsPlane3d :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsPlane3d(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsPlane3d :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsPlane3d(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddTriangle3d :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesAddTriangle3d(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsTriangle3d :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsTriangle3d(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsTriangle3d :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsTriangle3d(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddLine2d :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesAddLine2d(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsLine2d :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsLine2d(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsLine2d :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsLine2d(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddLine3d :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesAddLine3d(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int v) %code int result = IAttributesSetAttribute(attributeName, v); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsLine3d :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsLine3d(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsLine3d :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsLine3d(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int v) %code int result = IAttributesSetAttribute(index, v); %fail {result < 0} {getError();} %fun IAttributesAddTexture :: Int -> Int -> IO () %call (int attributeName) (int texture) %code int result = IAttributesAddTexture(attributeName, texture); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int texture) %code int result = IAttributesSetAttribute(attributeName, texture); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsTexture :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsTexture(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsTexture :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsTexture(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int texture) %code int result = IAttributesSetAttribute(index, texture); %fail {result < 0} {getError();} %fun IAttributesAddUserPointer :: Int -> Int -> IO () %call (int attributeName) (int userPointer) %code int result = IAttributesAddUserPointer(attributeName, userPointer); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int attributeName) (int userPointer) %code int result = IAttributesSetAttribute(attributeName, userPointer); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsUserPointer :: Int -> IO () %call (int attributeName) %code int result = IAttributesGetAttributeAsUserPointer(attributeName); %fail {result < 0} {getError();} %fun IAttributesGetAttributeAsUserPointer :: Int -> IO () %call (int index) %code int result = IAttributesGetAttributeAsUserPointer(index); %fail {result < 0} {getError();} %fun IAttributesSetAttribute :: Int -> Int -> IO () %call (int index) (int userPointer) %code int result = IAttributesSetAttribute(index, userPointer); %fail {result < 0} {getError();} %fun IXMLWriterIXMLWriter :: IO () %call %code int result = IXMLWriterIXMLWriter(); %fail {result < 0} {getError();} %fun IXMLWriterWriteXMLHeader :: IO () %call %code int result = IXMLWriterWriteXMLHeader(); %fail {result < 0} {getError();} %fun IXMLWriterWriteElement :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () %call (int name) (int empty) (int attr1Name) (int attr1Value) (int attr2Name) (int attr2Value) (int attr3Name) (int attr3Value) (int attr4Name) (int attr4Value) (int attr5Name) (int attr5Value) %code int result = IXMLWriterWriteElement(name, empty, attr1Name, attr1Value, attr2Name, attr2Value, attr3Name, attr3Value, attr4Name, attr4Value, attr5Name, attr5Value); %fail {result < 0} {getError();} %fun IXMLWriterWriteElement :: Int -> Int -> Int -> Int -> IO () %call (int name) (int empty) (int names) (int values) %code int result = IXMLWriterWriteElement(name, empty, names, values); %fail {result < 0} {getError();} %fun IXMLWriterWriteComment :: Int -> IO () %call (int comment) %code int result = IXMLWriterWriteComment(comment); %fail {result < 0} {getError();} %fun IXMLWriterWriteClosingTag :: Int -> IO () %call (int name) %code int result = IXMLWriterWriteClosingTag(name); %fail {result < 0} {getError();} %fun IXMLWriterWriteText :: Int -> IO () %call (int text) %code int result = IXMLWriterWriteText(text); %fail {result < 0} {getError();} %fun IXMLWriterWriteLineBreak :: IO () %call %code int result = IXMLWriterWriteLineBreak(); %fail {result < 0} {getError();}