-- GENERATED by C->Haskell Compiler, version 0.18.2 The shapeless maps, 31 Oct 2014 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/ImageSurface.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables, UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.ImageSurface
       (
         imageSurfaceNew
         -- * Hierarchy
         --
         -- $hierarchy

         -- * Functions
         --
         -- $functions

       )
where



import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Foreign.C.Types
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Hierarchy
import Graphics.UI.FLTK.LowLevel.Dispatch

imageSurfaceNew' :: (Int) -> (Int) -> IO ((Ptr ()))
imageSurfaceNew' a1 a2 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  imageSurfaceNew''_ a1' a2' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 26 "src/Graphics/UI/FLTK/LowLevel/ImageSurface.chs" #-}

imageSurfaceNew :: Size -> IO (Ref ImageSurface)
imageSurfaceNew (Size (Width w') (Height h')) = imageSurfaceNew' w' h' >>= toRef

imageSurfaceDestroy' :: (Ptr ()) -> IO ()
imageSurfaceDestroy' a1 =
  let {a1' = id a1} in 
  imageSurfaceDestroy''_ a1' >>
  return ()

{-# LINE 30 "src/Graphics/UI/FLTK/LowLevel/ImageSurface.chs" #-}

instance (impl ~ (IO ())) => Op (Destroy ()) ImageSurface orig impl where
  runOp _ _ image_surface = withRef image_surface $ \image_surfacePtr -> imageSurfaceDestroy' image_surfacePtr

className' :: (Ptr ()) -> IO ((String))
className' a1 =
  let {a1' = id a1} in 
  className''_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 34 "src/Graphics/UI/FLTK/LowLevel/ImageSurface.chs" #-}

instance (impl ~ ( IO (String))) => Op (ClassName ()) ImageSurface orig impl where
  runOp _ _ image_surface = withRef image_surface $ \image_surfacePtr -> className' image_surfacePtr

setCurrent' :: (Ptr ()) -> IO ()
setCurrent' a1 =
  let {a1' = id a1} in 
  setCurrent''_ a1' >>
  return ()

{-# LINE 38 "src/Graphics/UI/FLTK/LowLevel/ImageSurface.chs" #-}

instance (impl ~ ( IO ())) => Op (SetCurrent ()) ImageSurface orig impl where
  runOp _ _ image_surface = withRef image_surface $ \image_surfacePtr -> setCurrent' image_surfacePtr

draw' :: (Ptr ()) -> (Ptr ()) -> (Int) -> (Int) -> IO ()
draw' a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = id a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  draw''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 42 "src/Graphics/UI/FLTK/LowLevel/ImageSurface.chs" #-}

instance (Parent a Widget, impl ~ ( Ref a  -> Position -> IO ())) => Op (Draw ()) ImageSurface orig impl where
  runOp _ _ image_surface widget (Position (X delta_x) (Y delta_y)) = withRef image_surface $ \image_surfacePtr -> withRef widget $ \widgetPtr -> draw' image_surfacePtr widgetPtr delta_x delta_y


-- $hierarchy
-- @
-- "Graphics.UI.FLTK.LowLevel.ImageSurface"
-- @

-- $functions
-- @
-- className :: 'Ref' 'ImageSurface' -> 'IO' 'String'
--
-- destroy :: 'Ref' 'ImageSurface' -> 'IO' ()
--
-- draw:: ('Parent' a 'Widget') => 'Ref' 'ImageSurface' -> 'Ref' a -> 'Position' -> 'IO' ())
--
-- setCurrent :: 'Ref' 'ImageSurface' -> 'IO' ()
-- @

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/ImageSurface.chs.h Fl_Image_Surface_New"
  imageSurfaceNew''_ :: (CInt -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/ImageSurface.chs.h Fl_Image_Surface_Destroy"
  imageSurfaceDestroy''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/ImageSurface.chs.h Fl_Image_Surface_class_name"
  className''_ :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/ImageSurface.chs.h Fl_Image_Surface_set_current"
  setCurrent''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/ImageSurface.chs.h Fl_Image_Surface_draw"
  draw''_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))