module Graphics.UI.FLTK.LowLevel.XBMImage
    (
     xbmImageNew
     
     
     
    )
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Hierarchy
import Graphics.UI.FLTK.LowLevel.RGBImage
xbmImageNew' :: (String) -> IO ((Ptr ()))
xbmImageNew' a1 =
  let {a1' = unsafeToCString a1} in 
  xbmImageNew''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
xbmImageNew :: String -> IO (Either UnknownError (Ref XBMImage))
xbmImageNew filename' = do
  ptr <- xbmImageNew' filename'
  ref' <- (toRef ptr :: IO (Ref XBMImage))
  checkImage ref'
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/XBMImage.chs.h Fl_XBM_Image_New"
  xbmImageNew''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr ())))