-- 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\\CEGUI\\ClassFont.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. -- -- ClassFont.chs -- module HGamer3D.Bindings.CEGUI.ClassFont where import Foreign import Foreign.Ptr import Foreign.C import HGamer3D.Data.HG3DClass import HGamer3D.Data.Vector import HGamer3D.Data.Colour import HGamer3D.Data.Angle import HGamer3D.Bindings.CEGUI.Utils {-# LINE 40 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} import HGamer3D.Bindings.CEGUI.ClassPtr {-# LINE 41 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} import HGamer3D.Bindings.CEGUI.StructHG3DClass {-# LINE 42 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Destructor. delete :: HG3DClass -- ^ classpointer - pointer of Class instance which is going to be deleted. -> IO () -- ^ delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 47 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return the string holding the font name. getName :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ getName a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getName'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 52 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return the type of the font. getTypeName :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ getTypeName a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getTypeName'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 57 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return whether this Font isCodepointAvailable :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ cp - utf32 code point that is the subject of the query. -> IO (Bool) -- ^ return value - true if the font contains a mapping for code point isCodepointAvailable a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> isCodepointAvailable'_ a1' a2' a3' >>= \res -> peekBoolUtil a3'>>= \a3'' -> return (a3'') {-# LINE 63 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Enable or disable auto-scaling for this Font setAutoScaled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ auto_scaled - -- -- -> IO () -- ^ setAutoScaled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setAutoScaled'_ a1' a2' >>= \res -> return () {-# LINE 68 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return whether this Font isAutoScaled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isAutoScaled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isAutoScaled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 73 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return the pixel line spacing value for. getLineSpacing :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ y_scale - Scaling factor to be applied to the line spacing, where 1.0f is considered to be 'normal'. -> IO (Float) -- ^ return value - Number of pixels between vertical base lines, i.e. The minimum pixel space between two lines of text. getLineSpacing a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in alloca $ \a3' -> getLineSpacing'_ a1' a2' a3' >>= \res -> peekFloatConv a3'>>= \a3'' -> return (a3'') {-# LINE 79 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | return the exact pixel height of the font. getFontHeight :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ y_scale - Scaling factor to be applied to the height, where 1.0f is considered to be 'normal'. -> IO (Float) -- ^ return value - float value describing the pixel height of the font without any additional padding. getFontHeight a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in alloca $ \a3' -> getFontHeight'_ a1' a2' a3' >>= \res -> peekFloatConv a3'>>= \a3'' -> return (a3'') {-# LINE 85 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return the number of pixels from the top of the highest glyph to the baseline. getBaseline :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ y_scale - Scaling factor to be applied to the baseline distance, where 1.0f is considered to be 'normal'. -> IO (Float) -- ^ return value - pixel spacing from top of front glyphs to baseline getBaseline a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in alloca $ \a3' -> getBaseline'_ a1' a2' a3' >>= \res -> peekFloatConv a3'>>= \a3'' -> return (a3'') {-# LINE 91 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return the pixel width of the specified text if rendered with this Font getTextExtent :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ text - String object containing the text to return the rendered pixel width for. -> Float -- ^ x_scale - Scaling factor to be applied to each glyph's x axis when measuring the extent, where 1.0f is considered to be 'normal'. -> IO (Float) -- ^ return value - Number of pixels that getTextExtent a1 a2 a3 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> let {a3' = realToFrac a3} in alloca $ \a4' -> getTextExtent'_ a1' a2' a3' a4' >>= \res -> peekFloatConv a4'>>= \a4'' -> return (a4'') {-# LINE 98 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return the index of the closest text character in String textpixel getCharAtPixel :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ text - String object containing the text. -> Float -- ^ pixel - Specifies the (horizontal) pixel offset to return the character index for. -> Float -- ^ x_scale - Scaling factor to be applied to each glyph's x axis when measuring the text extent, where 1.0f is considered to be 'normal'. -> IO (Int) -- ^ return value - Returns a character index into String getCharAtPixel a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> let {a3' = realToFrac a3} in let {a4' = realToFrac a4} in alloca $ \a5' -> getCharAtPixel'_ a1' a2' a3' a4' a5' >>= \res -> peekIntConv a5'>>= \a5'' -> return (a5'') {-# LINE 106 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Return the index of the closest text character in String textstart_charpixel getCharAtPixel2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ text - String object containing the text. -> Int -- ^ start_char - index of the first character to consider. This is the lowest value that will be returned from the call. -> Float -- ^ pixel - Specifies the (horizontal) pixel offset to return the character index for. -> Float -- ^ x_scale - Scaling factor to be applied to each glyph's x axis when measuring the text extent, where 1.0f is considered to be 'normal'. -> IO (Int) -- ^ return value - Returns a character index into String getCharAtPixel2 a1 a2 a3 a4 a5 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> let {a3' = fromIntegral a3} in let {a4' = realToFrac a4} in let {a5' = realToFrac a5} in alloca $ \a6' -> getCharAtPixel2'_ a1' a2' a3' a4' a5' a6' >>= \res -> peekIntConv a6'>>= \a6'' -> return (a6'') {-# LINE 115 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Sets the default resource group to be used when loading font data. setDefaultResourceGroup :: String -- ^ resourceGroup - String describing the default resource group identifier to be used. -> IO () -- ^ return value - Nothing. setDefaultResourceGroup a1 = withCString a1 $ \a1' -> setDefaultResourceGroup'_ a1' >>= \res -> return () {-# LINE 119 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} -- | Returns the default resource group currently set for Fonts. getDefaultResourceGroup :: IO (String) -- ^ return value - String describing the default resource group identifier that will be used when loading font data. getDefaultResourceGroup = alloc64k $ \a1' -> getDefaultResourceGroup'_ a1' >>= \res -> peekCString a1'>>= \a1'' -> return (a1'') {-# LINE 123 ".\\HGamer3D\\Bindings\\CEGUI\\ClassFont.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getName" getName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getTypeName" getTypeName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_isCodepointAvailable" isCodepointAvailable'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_setAutoScaled" setAutoScaled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_isAutoScaled" isAutoScaled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getLineSpacing" getLineSpacing'_ :: ((HG3DClassPtr) -> (CFloat -> ((Ptr CFloat) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getFontHeight" getFontHeight'_ :: ((HG3DClassPtr) -> (CFloat -> ((Ptr CFloat) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getBaseline" getBaseline'_ :: ((HG3DClassPtr) -> (CFloat -> ((Ptr CFloat) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getTextExtent" getTextExtent'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getCharAtPixel" getCharAtPixel'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CFloat -> (CFloat -> ((Ptr CInt) -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getCharAtPixel2" getCharAtPixel2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CInt -> (CFloat -> (CFloat -> ((Ptr CInt) -> (IO ()))))))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_setDefaultResourceGroup" setDefaultResourceGroup'_ :: ((Ptr CChar) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassFont.chs.h cegui_fnt_getDefaultResourceGroup" getDefaultResourceGroup'_ :: ((Ptr CChar) -> (IO ()))