-- GENERATED by C->Haskell Compiler, version 0.16.3 Crystal Seed, 24 Jan 2009 (Haskell) -- Edit the ORIGNAL .chs file instead! {-# LINE 1 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-}{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE TypeSynonymInstances #-} -- This source file is part of HGamer3D -- (A project to enable 3D game development in Haskell) -- For the latest info, see http://www.althainz.de/HGamer3D.html -- -- (c) 2011, 2012 Peter Althainz -- -- Licensed under the Apache License, Version 2.0 (the "License"); -- you may not use this file except in compliance with the License. -- You may obtain a copy of the License at -- -- http://www.apache.org/licenses/LICENSE-2.0 -- -- Unless required by applicable law or agreed to in writing, software -- distributed under the License is distributed on an "AS IS" BASIS, -- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. -- See the License for the specific language governing permissions and -- limitations under the License. -- -- ClassException.chs -- module HGamer3D.Bindings.Ogre.ClassException where import C2HS import Foreign import Foreign.Ptr import Foreign.C import Monad (liftM, liftM2) import HGamer3D.Data.HG3DClass import HGamer3D.Data.Vector import HGamer3D.Data.Colour import HGamer3D.Data.Angle import HGamer3D.Bindings.Ogre.Utils {-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Default constructor. new :: Int -- ^ number -> String -- ^ description -> String -- ^ source -> IO (HG3DClass) -- ^ new a1 a2 a3 = let {a1' = fromIntegral a1} in withCString a2 $ \a2' -> withCString a3 $ \a3' -> alloca $ \a4' -> new'_ a1' a2' a3' a4' >>= \res -> peek a4'>>= \a4'' -> return (a4'') {-# LINE 52 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Needed for compatibility with std::exception. delete :: HG3DClass -- ^ classpointer - pointer of Class instance which is going to be deleted. -> IO () -- ^ delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 56 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Returns a string with the full description of this error. The description contains the error number, the description supplied by the thrower, what routine threw the exception, and will also supply extra platform-specific information where applicable. For example - in the case of a rendering library error, the description of the error will include both the place in which OGRE found the problem, and a text description from the 3D rendering library, if available. getFullDescription :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ getFullDescription a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getFullDescription'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 61 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Gets the error code. getNumber :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ getNumber a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getNumber'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 66 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Gets the source function. getSource :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ getSource a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getSource'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 71 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Gets source file name. getFile :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ getFile a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getFile'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 76 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Gets line number. getLine :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ getLine a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getLine'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 81 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Returns a string with only the 'description' field of this exception. Use getFullDescriptionto get a full description of the error including line number, error number and what function threw the exception. getDescription :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ getDescription a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getDescription'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 86 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} -- | Override std::exception::what. what :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ what a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> what'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 91 ".\\HGamer3D\\Bindings\\Ogre\\ClassException.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_construct" new'_ :: (CInt -> ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_getFullDescription" getFullDescription'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_getNumber" getNumber'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_getSource" getSource'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_getFile" getFile'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_getLine" getLine'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_getDescription" getDescription'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassException.chs.h ogre_exc_what" what'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))