-- 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\\ClassEditbox.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. -- -- ClassEditbox.chs -- module HGamer3D.Bindings.CEGUI.ClassEditbox 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\\ClassEditbox.chs" #-} import HGamer3D.Bindings.CEGUI.ClassPtr {-# LINE 41 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} import HGamer3D.Bindings.CEGUI.StructHG3DClass {-# LINE 42 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return true if the Editbox hasInputFocus :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ hasInputFocus a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> hasInputFocus'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 48 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return true if the Editbox isReadOnly :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ return value - true if the isReadOnly a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isReadOnly'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 53 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return true if the text for the Editbox isTextMasked :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ return value - true if the isTextMasked a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isTextMasked'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 58 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return true if the Editbox - Details: It is possible to programmatically set 'invalid' text for the Editbox --Validation is performed by means of a regular expression. If the text matches the regex, the text is said to have passed validation. If the text does not match with the regex then the text fails validation. isTextValid :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isTextValid a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isTextValid'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 63 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return the currently set validation string - Details: Validation is performed by means of a regular expression. If the text matches the regex, the text is said to have passed validation. If the text does not match with the regex then the text fails validation. getValidationString :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ return value - String object containing the current validation regex data getValidationString a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getValidationString'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 68 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return the current position of the carat. getCaratIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - Index of the insert carat relative to the start of the text. getCaratIndex a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCaratIndex'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 73 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return the current selection start point. getSelectionStartIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - Index of the selection start point relative to the start of the text. If no selection is defined this function returns the position of the carat. getSelectionStartIndex a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSelectionStartIndex'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 78 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return the current selection end point. getSelectionEndIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - Index of the selection end point relative to the start of the text. If no selection is defined this function returns the position of the carat. getSelectionEndIndex a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSelectionEndIndex'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 83 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return the length of the current selection (in code points / characters). getSelectionLength :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - Number of code points (or characters) contained within the currently defined selection. getSelectionLength a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSelectionLength'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 88 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return the utf32 code point used when rendering masked text. getMaskCodePoint :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - utf32 code point value representing the Unicode code point that will be rendered instead of the getMaskCodePoint a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getMaskCodePoint'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 93 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | return the maximum text length set for this Editbox - Details: Depending on the validation string set, the actual length of text that can be entered may be less than the value returned here (it will never be more). getMaxTextLength :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - The maximum number of code points (characters) that can be entered into this getMaxTextLength a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getMaxTextLength'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 98 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | Specify whether the Editbox setReadOnly :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ setting - true if the Editbox is read only and can't be edited by the user, false if the Editbox is not read only and may be edited by the user. -> IO () -- ^ return value - Nothing. setReadOnly a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setReadOnly'_ a1' a2' >>= \res -> return () {-# LINE 103 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | Specify whether the text for the Editbox setTextMasked :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ setting - -- -- -> IO () -- ^ return value - Nothing. setTextMasked a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setTextMasked'_ a1' a2' >>= \res -> return () {-# LINE 108 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | Set the text validation string. - Details: Validation is performed by means of a regular expression. If the text matches the regex, the text is said to have passed validation. If the text does not match with the regex then the text fails validation. setValidationString :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ validation_string - String object containing the validation regex data to be used. -> IO () -- ^ return value - Nothing. setValidationString a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> setValidationString'_ a1' a2' >>= \res -> return () {-# LINE 113 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | Set the current position of the carat. setCaratIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ carat_pos - New index for the insert carat relative to the start of the text. If the value specified is greater than the number of characters in the Editbox, the carat is positioned at the end of the text. -> IO () -- ^ return value - Nothing. setCaratIndex a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setCaratIndex'_ a1' a2' >>= \res -> return () {-# LINE 118 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | Define the current selection for the Editbox setSelection :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ start_pos - Index of the starting point for the selection. If this value is greater than the number of characters in the Editbox, the selection start will be set to the end of the text. -> Int -- ^ end_pos - Index of the ending point for the selection. If this value is greater than the number of characters in the Editbox, the selection end will be set to the end of the text. -> IO () -- ^ return value - Nothing. setSelection a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromIntegral a3} in setSelection'_ a1' a2' a3' >>= \res -> return () {-# LINE 124 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | set the utf32 code point used when rendering masked text. setMaskCodePoint :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ code_point - utf32 code point value representing the Unicode code point that should be rendered instead of the Editbox text when rendering in masked mode. -> IO () -- ^ return value - Nothing. setMaskCodePoint a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setMaskCodePoint'_ a1' a2' >>= \res -> return () {-# LINE 129 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | set the maximum text length for this Editbox - Details: Depending on the validation string set, the actual length of text that can be entered may be less than the value set here (it will never be more). setMaxTextLength :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ max_len - The maximum number of code points (characters) that can be entered into this Editbox. -> IO () -- ^ return value - Nothing. setMaxTextLength a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setMaxTextLength'_ a1' a2' >>= \res -> return () {-# LINE 134 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | Constructor for Editbox new :: String -- ^ type -> String -- ^ name -> IO (HG3DClass) -- ^ new a1 a2 = withCString a1 $ \a1' -> withCString a2 $ \a2' -> alloca $ \a3' -> new'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 140 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} -- | Destructor for Editbox delete :: HG3DClass -- ^ classpointer - pointer of Class instance which is going to be deleted. -> IO () -- ^ delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 144 ".\\HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_hasInputFocus" hasInputFocus'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_isReadOnly" isReadOnly'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_isTextMasked" isTextMasked'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_isTextValid" isTextValid'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_getValidationString" getValidationString'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_getCaratIndex" getCaratIndex'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_getSelectionStartIndex" getSelectionStartIndex'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_getSelectionEndIndex" getSelectionEndIndex'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_getSelectionLength" getSelectionLength'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_getMaskCodePoint" getMaskCodePoint'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_getMaxTextLength" getMaxTextLength'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_setReadOnly" setReadOnly'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_setTextMasked" setTextMasked'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_setValidationString" setValidationString'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_setCaratIndex" setCaratIndex'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_setSelection" setSelection'_ :: ((HG3DClassPtr) -> (CInt -> (CInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_setMaskCodePoint" setMaskCodePoint'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_setMaxTextLength" setMaxTextLength'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_construct" new'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\CEGUI\\ClassEditbox.chs.h cegui_edtbx_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ()))