{-# LANGUAGE ForeignFunctionInterface #-} module Irrlicht where import Foreign.GreenCard data MeshPtr = MeshPtr Int data NodePtr = NodePtr Int data TexturePtr = TexturePtr Int %#include "irrlicht_interface.h" %C enum drivertype {EDT_NULL, EDT_SOFTWARE, EDT_BURNINGSVIDEO, EDT_DIRECT3D8, EDT_DIRECT3D9, EDT_OPENGL}; %C enum materialflag {EMF_WIREFRAME = 0x1, EMF_POINTCLOUD = 0x2, EMF_GOURARD_SHADING = 0x4, EMF_LIGHTING = 0x8, EMF_ZBUFFER = 0x10, EMF_ZWRITE_ENABLE = 0x20, EMF_BACK_FACE_CULLING = 0x40, EMF_FRONT_FACE_CULLING = 0x80, EMF_BILINEAR_FILTER = 0x100, EMF_TRILINEAR_FILTER = 0x200, EMF_ANISOTROPIC_FILTER = 0x400, EMF_FOG_ENABLE = 0x800, EMF_NORMALIZE_NORMALS = 0x1000, EMF_TEXTURE_WRAP = 0x2000, EMF_ANTI_ALIASING = 0x4000, EMF_COLOR_MASK = 0x8000, EMF_COLOR_MATERIAL = 0x100000}; %C enum md2animationtype {EMAT_STAND, EMAT_RUN, EMAT_ATTACK, EMAT_PAIN_A, EMAT_PAIN_B, EMAT_PAIN_C, EMAT_JUMP, EMAT_FLIP, EMAT_SALUTE, EMAT_FALLBACK, EMAT_WAVE, EMAT_POINT, EMAT_CROUCH_STAND, EMAT_CROUCH_WALK, EMAT_CROUCH_ATTACK, EMAT_CROUCH_PAIN, EMAT_CROUCH_DEATH, EMAT_DEATH_FALLBACK, EMAT_DEATH_FALLFORWARD, EMAT_DEATH_FALLBACKSLOW, EMAT_BOOM, EMAT_COUNT}; %enum VideoDriverType Int [EDT_NULL, EDT_SOFTWARE, EDT_BURNINGSVIDEO, EDT_DIRECT3D8, EDT_DIRECT3D9, EDT_OPENGL] %enum VideoMaterialFlag Int [EMF_WIREFRAME, EMF_POINTCLOUD, EMF_GOURARD_SHADING, EMF_LIGHTING, EMF_ZBUFFER, EMF_ZWRITE_ENABLE, EMF_BACK_FACE_CULLING, EMF_FRONT_FACE_CULLING, EMF_BILINEAR_FILTER, EMF_TRILINEAR_FILTER, EMF_ANISOTROPIC_FILTER, EMF_FOG_ENABLE, EMF_NORMALIZE_NORMALS, EMF_TEXTURE_WRAP, EMF_ANTI_ALIASING, EMF_COLOR_MASK, EMF_COLOR_MATERIAL] %enum SceneMd2AnimationType Int [EMAT_STAND, EMAT_RUN, EMAT_ATTACK, EMAT_PAIN_A, EMAT_PAIN_B, EMAT_PAIN_C, EMAT_JUMP, EMAT_FLIP, EMAT_SALUTE, EMAT_FALLBACK, EMAT_WAVE, EMAT_POINT, EMAT_CROUCH_STAND, EMAT_CROUCH_WALK, EMAT_CROUCH_ATTACK, EMAT_CROUCH_PAIN, EMAT_CROUCH_DEATH, EMAT_DEATH_FALLBACK, EMAT_DEATH_FALLFORWARD, EMAT_DEATH_FALLBACKSLOW, EMAT_BOOM, EMAT_COUNT] {- Device -} %fun GetEvent :: IO Int %call %code int result = GetEvent(); %result (int result) %fun GetCharEvent :: IO Char %call %code char result = GetCharEvent(); %result (char result) %fun DeviceSetEventReceiver :: Int -> IO () %call (int control) %code int result = DeviceSetEventReceiver(control); %fail {result < 0} {getError();} %fun DeviceSetWindowCaption :: String -> IO () %call (string caption) %code int result = DeviceSetWindowCaption(caption); %fail {result < 0} {getError();} %fun DeviceRun :: IO Int %call %code int result = DeviceRun(); %fail {result < 0} {getError();} %result (int result) %fun DeviceDrop :: IO () %call %code int result = DeviceDrop(); %fail {result < 0} {getError();} %fun IrrCreateDevice :: VideoDriverType -> Int -> Int -> Bool -> Bool -> Bool -> IO () %call (videoDriverType dtype) (int sizex) (int sizey) (bool fullscreen) (bool stencilbuffer) (bool vsync) %code int result = IrrCreateDevice(dtype, sizex, sizey, fullscreen, stencilbuffer, vsync); %fail {result < 0} {getError();} {- Gui -} %fun GuiAddStaticText :: String -> Int -> Int -> Int -> Int -> IO () %call (string text) (int topleftx) (int toplefty) (int lowrightx) (int lowrighty) %code int result = GuiAddStaticText(text, topleftx, toplefty, lowrightx, lowrighty); %fail {result < 0} {getError();} %fun GuiDrawAll :: IO () %call %code int result = GuiDrawAll(); %fail {result < 0} {getError();} {- VideoDriver -} %fun VideoBeginScene :: Bool -> Bool -> Int -> Int -> Int -> Int -> IO () %call (bool a) (bool b) (int colr) (int colg) (int colb) (int colt) %code int result = VideoBeginScene(a, b, colr, colg, colb, colt); %fail {result < 0} {getError();} %fun VideoEndScene :: IO () %call %code int result = VideoEndScene(); %fail {result < 0} {getError();} %fun VideoGetTexture :: String -> IO TexturePtr %call (string texture) %code int pTexture = VideoGetTexture(texture); %fail {pTexture == 0} {getError();} %result (TexturePtr (int pTexture)) {- Scene -} %fun SceneDrawAll :: IO () %call %code int result = SceneDrawAll(); %fail {result < 0} {getError();} %fun SceneGetMesh :: String -> IO MeshPtr %call (string mesh) %code int pMesh = SceneGetMesh(mesh); %fail {pMesh == 0} {getError();} %result (MeshPtr (int pMesh)) %fun SceneAddAnimatedMeshSceneNode :: MeshPtr -> IO NodePtr %call (MeshPtr (int pMesh)) %code int pNode = SceneAddAnimatedMeshSceneNode(pMesh); %fail {pNode == 0} {getError();} %result (NodePtr (int pNode)) %fun SceneAddCameraSceneNode :: (Int, Int, Int) -> (Int, Int, Int) -> IO () %call (int posx, int posy, int posz) (int tox, int toy, int toz) %code int result = SceneAddCameraSceneNode(posx, posy, posz, tox, toy, toz); %fail {result < 0} {getError();} %fun SceneAddOctTreeSceneNode :: MeshPtr -> IO NodePtr %call (MeshPtr (int pMesh)) %code int pNode = SceneAddOctTreeSceneNode(pMesh); %fail {pNode == 0} {getError();} %result (NodePtr (int pNode)) %fun SceneNodeSetPosition :: (Int, Int, Int) -> NodePtr -> IO () %call (int posx, int posy, int posz) (NodePtr (int pNode)) %code int result = SceneNodeSetPosition( posx, posy,posz, pNode); %fail {result <0}{getError();} %fun SceneAddCameraSceneNodeFPS :: IO () %code int result = SceneAddCameraSceneNodeFPS(); %fail {result <0}{getError();} {- Node -} %fun NodeSetMaterialTexture :: NodePtr -> TexturePtr -> IO () %call (NodePtr (int pNode)) (TexturePtr (int pTexture)) %code int result = NodeSetMaterialTexture(pNode, pTexture); %fail {result < 0} {getError();} %fun NodeSetMaterialFlag :: NodePtr -> VideoMaterialFlag -> Bool -> IO () %call (NodePtr (int pNode)) (videoMaterialFlag mflag) (bool value) %code int result = NodeSetMaterialFlag(pNode, mflag, value); %fail {result < 0} {getError();} %fun NodeSetMd2Animation :: NodePtr -> SceneMd2AnimationType -> IO () %call (NodePtr (int pNode)) (sceneMd2AnimationType atype) %code int result = NodeSetMd2Animation(pNode, atype); %fail {result < 0} {getError();} {- Files -} %fun FileSystemAddZipFileArchive :: String -> IO () %call (string file) %code int result = FileSystemAddZipFileArchive(file); %fail {result < 0} {getError();} {- Timer -} %fun GetVirtualTime :: Int %call %code int result = GetVirtualTime();