module Graphics.UI.FLTK.LowLevel.Pixmap
 (
  pixmapNew
  
  
  
  
  
  
 )
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Foreign.C.Types
import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
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
flPixmapNew' :: (Ptr (Ptr CChar)) -> IO ((Ptr ()))
flPixmapNew' a1 =
  let {a1' = id a1} in 
  flPixmapNew''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
pixmapNew :: PixmapHs -> IO (Ref Pixmap)
pixmapNew pixmap = withPixmap pixmap (\ptr -> flPixmapNew' ptr >>= toRef)
flPixmapDestroy' :: (Ptr ()) -> IO ((()))
flPixmapDestroy' a1 =
  let {a1' = id a1} in 
  flPixmapDestroy''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
instance (impl ~ (IO ())) => Op (Destroy ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> flPixmapDestroy' pixmapPtr
w' :: (Ptr ()) -> IO ((Int))
w' a1 =
  let {a1' = id a1} in 
  w''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
instance (impl ~ ( IO (Int))) => Op (GetW ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> w' pixmapPtr
h' :: (Ptr ()) -> IO ((Int))
h' a1 =
  let {a1' = id a1} in 
  h''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
instance (impl ~ ( IO (Int))) => Op (GetH ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> h' pixmapPtr
d' :: (Ptr ()) -> IO ((Int))
d' a1 =
  let {a1' = id a1} in 
  d''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
instance (impl ~ ( IO (Int))) => Op (GetD ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> d' pixmapPtr
ld' :: (Ptr ()) -> IO ((Int))
ld' a1 =
  let {a1' = id a1} in 
  ld''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
instance (impl ~ ( IO (Int))) => Op (GetLd ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> ld' pixmapPtr
count' :: (Ptr ()) -> IO ((Int))
count' a1 =
  let {a1' = id a1} in 
  count''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
instance (impl ~ ( IO (Int))) => Op (GetCount ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> count' pixmapPtr
copyWithWH' :: (Ptr ()) -> (Int) -> (Int) -> IO ((Ptr ()))
copyWithWH' a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  copyWithWH''_ a1' a2' a3' >>= \res ->
  let {res' = id res} in
  return (res')
copy' :: (Ptr ()) -> IO ((Ptr ()))
copy' a1 =
  let {a1' = id a1} in 
  copy''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')
instance (impl ~ ( Maybe Size -> IO (Maybe (Ref Pixmap)))) => Op (Copy ()) Pixmap orig impl where
  runOp _ _ pixmap size' = case size' of
    Just (Size (Width w) (Height h)) -> withRef pixmap $ \pixmapPtr -> copyWithWH' pixmapPtr w h >>= toMaybeRef
    Nothing -> withRef pixmap $ \pixmapPtr -> copy' pixmapPtr >>= toMaybeRef
colorAverage' :: (Ptr ()) -> (Color) -> (Float) -> IO ()
colorAverage' a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = cFromColor a2} in 
  let {a3' = realToFrac a3} in 
  colorAverage''_ a1' a2' a3' >>
  return ()
instance (impl ~ (Color -> Float ->  IO ())) => Op (ColorAverage ()) Pixmap orig impl where
  runOp _ _ pixmap c i = withRef pixmap $ \pixmapPtr -> colorAverage' pixmapPtr c i
inactive' :: (Ptr ()) -> IO ()
inactive' a1 =
  let {a1' = id a1} in 
  inactive''_ a1' >>
  return ()
instance (impl ~ ( IO ())) => Op (Inactive ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> inactive' pixmapPtr
desaturate' :: (Ptr ()) -> IO ()
desaturate' a1 =
  let {a1' = id a1} in 
  desaturate''_ a1' >>
  return ()
instance (impl ~ ( IO ())) => Op (Desaturate ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> desaturate' pixmapPtr
drawWithCxCy' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
drawWithCxCy' a1 a2 a3 a4 a5 a6 a7 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  let {a7' = fromIntegral a7} in 
  drawWithCxCy''_ a1' a2' a3' a4' a5' a6' a7' >>
  return ()
drawWithCx' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
drawWithCx' a1 a2 a3 a4 a5 a6 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  drawWithCx''_ a1' a2' a3' a4' a5' a6' >>
  return ()
drawWithCy' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
drawWithCy' a1 a2 a3 a4 a5 a6 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = fromIntegral a6} in 
  drawWithCy''_ a1' a2' a3' a4' a5' a6' >>
  return ()
drawWith' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
drawWith' a1 a2 a3 a4 a5 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  drawWith''_ a1' a2' a3' a4' a5' >>
  return ()
instance (impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ())) => Op (DrawResize ()) Pixmap orig impl where
  runOp _ _ pixmap (Position (X x) (Y y)) (Size (Width w) (Height h)) xOffset yOffset =
    case (xOffset, yOffset) of
      (Just (X xOff), Just (Y yOff)) ->
        withRef pixmap $ \pixmapPtr -> drawWithCxCy' pixmapPtr x y w h (fromIntegral xOff) (fromIntegral yOff)
      (Just (X xOff), Nothing) ->
        withRef pixmap $ \pixmapPtr -> drawWithCx' pixmapPtr x y w h (fromIntegral xOff)
      (Nothing, Just (Y yOff)) ->
        withRef pixmap $ \pixmapPtr -> drawWithCy' pixmapPtr x y w h (fromIntegral yOff)
      (Nothing, Nothing) ->
        withRef pixmap $ \pixmapPtr -> drawWith' pixmapPtr x y w h
draw' :: (Ptr ()) -> (Int) -> (Int) -> IO ()
draw' a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  draw''_ a1' a2' a3' >>
  return ()
instance (impl ~ (Position ->  IO ())) => Op (Draw ()) Pixmap orig impl where
  runOp _ _ image (Position (X x_pos') (Y y_pos')) = withRef image $ \imagePtr -> draw' imagePtr x_pos' y_pos'
uncache' :: (Ptr ()) -> IO ()
uncache' a1 =
  let {a1' = id a1} in 
  uncache''_ a1' >>
  return ()
instance (impl ~ ( IO ())) => Op (Uncache ()) Pixmap orig impl where
  runOp _ _ pixmap = withRef pixmap $ \pixmapPtr -> uncache' pixmapPtr
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_New"
  flPixmapNew''_ :: ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_Destroy"
  flPixmapDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_w"
  w''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_h"
  h''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_d"
  d''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_ld"
  ld''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_count"
  count''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_copy_with_w_h"
  copyWithWH''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_copy"
  copy''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_color_average"
  colorAverage''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (C2HSImp.CFloat -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_inactive"
  inactive''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_desaturate"
  desaturate''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_draw_with_cx_cy"
  drawWithCxCy''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_draw_with_cx"
  drawWithCx''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_draw_with_cy"
  drawWithCy''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_draw_with"
  drawWith''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_draw"
  draw''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Pixmap.chs.h Fl_Pixmap_uncache"
  uncache''_ :: ((C2HSImp.Ptr ()) -> (IO ()))