-- GENERATED by C->Haskell Compiler, version 0.28.6 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


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

       -- * Functions
       --
       -- $functions
       )
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_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
import qualified Data.Vector.Storable as DVS
import Control.Exception

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

{-# LINE 29 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

rgbImageNew_WithD' :: (Ptr CUChar) -> (Int) -> (Int) -> (Int) -> IO ((Ptr ()))
rgbImageNew_WithD' a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  rgbImageNew_WithD''_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
;
rgbImageNew_WithLD' :: (Ptr CUChar) -> (Int) -> (Int) -> (Int) -> IO ((Ptr ()))
rgbImageNew_WithLD' a1 a2 a3 a4 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  rgbImageNew_WithLD''_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')
;
rgbImageNew_WithD_LD' :: (Ptr CUChar) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((Ptr ()))
rgbImageNew_WithD_LD' :: Ptr CUChar -> Int -> Int -> Int -> Int -> IO (Ptr ())
rgbImageNew_WithD_LD' a1 :: Ptr CUChar
a1 a2 :: Int
a2 a3 :: Int
a3 a4 :: Int
a4 a5 :: Int
a5 =
  let {a1' :: Ptr CUChar
a1' = Ptr CUChar -> Ptr CUChar
forall a. a -> a
id Ptr CUChar
a1} in 
  let {a2' :: CInt
a2' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a2} in 
  let {a3' :: CInt
a3' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a3} in 
  let {a4' :: CInt
a4' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a4} in 
  let {a5' :: CInt
a5' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a5} in 
  Ptr CUChar -> CInt -> CInt -> CInt -> CInt -> IO (Ptr ())
rgbImageNew_WithD_LD''_ Ptr CUChar
a1' CInt
a2' CInt
a3' CInt
a4' CInt
a5' IO (Ptr ()) -> (Ptr () -> IO (Ptr ())) -> IO (Ptr ())
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \res :: Ptr ()
res ->
  let {res' :: Ptr ()
res' = Ptr () -> Ptr ()
forall a. a -> a
id Ptr ()
res} in
  Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr ()
res')
;
rgbImageNew :: DVS.Vector CUChar -> Size -> Maybe Depth  -> Maybe LineSize -> IO (Ref RGBImage)
rgbImageNew :: Vector CUChar
-> Size -> Maybe Depth -> Maybe LineSize -> IO (Ref RGBImage)
rgbImageNew bits' :: Vector CUChar
bits' (Size (Width width' :: Int
width') (Height height' :: Int
height')) depth' :: Maybe Depth
depth' linesize' :: Maybe LineSize
linesize' = do
  Vector CUChar
-> (Ptr CUChar -> IO (Ref RGBImage)) -> IO (Ref RGBImage)
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
DVS.unsafeWith Vector CUChar
bits' ((Ptr CUChar -> IO (Ref RGBImage)) -> IO (Ref RGBImage))
-> (Ptr CUChar -> IO (Ref RGBImage)) -> IO (Ref RGBImage)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr CUChar
ptr -> do
    (Ref RGBImage
ref :: Ref RGBImage) <-
       case (Maybe Depth
depth', Maybe LineSize
linesize') of
         (Just (Depth imageDepth :: Int
imageDepth) , Nothing) -> Ptr CUChar -> Int -> Int -> Int -> IO (Ptr ())
rgbImageNew_WithD' Ptr CUChar
ptr Int
width' Int
height' Int
imageDepth IO (Ptr ()) -> (Ptr () -> IO (Ref RGBImage)) -> IO (Ref RGBImage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr () -> IO (Ref RGBImage)
forall a. Ptr () -> IO (Ref a)
toRef
         (Nothing, Just (LineSize l' :: Int
l')) -> Ptr CUChar -> Int -> Int -> Int -> IO (Ptr ())
rgbImageNew_WithLD' Ptr CUChar
ptr Int
width' Int
height' Int
l' IO (Ptr ()) -> (Ptr () -> IO (Ref RGBImage)) -> IO (Ref RGBImage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr () -> IO (Ref RGBImage)
forall a. Ptr () -> IO (Ref a)
toRef
         (Just (Depth imageDepth :: Int
imageDepth), Just (LineSize l' :: Int
l')) -> Ptr CUChar -> Int -> Int -> Int -> Int -> IO (Ptr ())
rgbImageNew_WithD_LD' Ptr CUChar
ptr Int
width' Int
height' Int
imageDepth Int
l' IO (Ptr ()) -> (Ptr () -> IO (Ref RGBImage)) -> IO (Ref RGBImage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr () -> IO (Ref RGBImage)
forall a. Ptr () -> IO (Ref a)
toRef
         (Nothing, Nothing) -> Ptr CUChar -> Int -> Int -> IO (Ptr ())
rgbImageNew' Ptr CUChar
ptr Int
width' Int
height' IO (Ptr ()) -> (Ptr () -> IO (Ref RGBImage)) -> IO (Ref RGBImage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr () -> IO (Ref RGBImage)
forall a. Ptr () -> IO (Ref a)
toRef
    r <- copy ref Nothing
    case Maybe (Ref RGBImage)
r of
      Nothing -> IOError -> IO (Ref RGBImage)
forall e a. Exception e => e -> IO a
throwIO (String -> IOError
userError "rgbImageNew: could not create RGB Image.")
      Just r :: Ref RGBImage
r -> Ref RGBImage -> IO (Ref RGBImage)
forall (m :: * -> *) a. Monad m => a -> m a
return Ref RGBImage
r

-- | Check that the given RGBImage (or subclass of RGBImage) has a non-zero width.
--
-- For the most part you don't have worry about all the ugly constraints.
-- If you're interested, they check that the given reference is an RGBImage, which supports 'getW' and 'destroy'.
checkImage :: (
                Parent orig RGBImage,
                Match x ~ FindOp orig orig (GetW ()),
                Op (GetW ()) x orig (IO Int),
                Match y ~ FindOp orig orig (Destroy ()),
                Op (Destroy ()) y orig (IO ())
               )
               => Ref orig -> IO (Either UnknownError (Ref orig))
checkImage ref' = a3 :: Int
do
  imageWidth <- getW ref'
  if (imageWidth == (0 :: Int))
   then do
     () <- destroy ref'
     return (Left UnknownError)
   else (return (Right ref'))

flImageDestroy' :: (Ptr ()) -> IO ((()))
flImageDestroy' a1 =
  let {a2' :: CUInt
a1' = id a1} in 
  flImageDestroy''_ a1' >>= \res ->
  let {res' = id res} in
  () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return (res')

{-# LINE 67 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ (IO ())) => Op (Destroy ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> flImageDestroy' imagePtr
w' :: (Ptr ()) -> IO ((Int))
w' a1 =
  let {a1' = id a1} in 
  w''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 70 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetW ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> w' imagePtr
h' :: (Ptr ()) -> IO ((Int))
h' a1 =
  let {a1' = id a1} in 
  h''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 73 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetH ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> h' imagePtr
d' :: (Ptr ()) -> IO ((Int))
d' a1 =
  let {a1' = id a1} in 
  d''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 76 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetD ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> d' imagePtr
ld' :: (Ptr ()) -> IO ((Int))
ld' a1 =
  let {a1' = id a1} in 
  ld''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 79 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetLd ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> ld' imagePtr
count' :: (Ptr ()) -> IO ((Int))
count' a1 =
  let {a1' = id a1} in 
  count''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 82 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetCount ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> count' imagePtr

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')

{-# LINE 86 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

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

{-# LINE 87 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( Maybe Size -> IO (Maybe (Ref orig)))) => Op (Copy ()) RGBImage orig impl where
  runOp _ _ image size' = case size' of
    Just (Size (Width imageWidth) (Height imageHeight)) ->
        withRef image $ \imagePtr -> copyWithWH' imagePtr imageWidth imageHeight >>= toMaybeRef
    Nothing -> withRef image $ \imagePtr -> copy' imagePtr >>= 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 ()

{-# LINE 94 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ (Color -> Float ->  IO ())) => Op (ColorAverage ()) RGBImage orig impl where
  runOp _ _ image c i = withRef image $ \imagePtr -> colorAverage' imagePtr c i

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

{-# LINE 98 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO ())) => Op (Inactive ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> inactive' imagePtr

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

{-# LINE 102 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO ())) => Op (Desaturate ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> desaturate' imagePtr

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 ()

{-# LINE 106 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

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 ()

{-# LINE 107 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

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 ()

{-# LINE 108 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

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 ()

{-# LINE 109 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ())) => Op (DrawResize ()) RGBImage orig impl where
  runOp _ _ image (Position (X imageX) (Y imageY)) (Size (Width imageWidth) (Height imageHeight)) xOffset yOffset =
    case (xOffset, yOffset) of
      (Just (X xOff), Just (Y yOff)) ->
        withRef image $ \imagePtr -> drawWithCxCy' imagePtr imageX imageY imageWidth imageHeight (fromIntegral xOff) (fromIntegral yOff)
      (Just (X xOff), Nothing) ->
        withRef image $ \imagePtr -> drawWithCx' imagePtr imageX imageY imageWidth imageHeight (fromIntegral xOff)
      (Nothing, Just (Y yOff)) ->
        withRef image $ \imagePtr -> drawWithCy' imagePtr imageX imageY imageWidth imageHeight (fromIntegral yOff)
      (Nothing, Nothing) ->
        withRef image $ \imagePtr -> drawWith' imagePtr imageX imageY imageWidth imageHeight

draw' :: (Ptr ()) -> (Int) -> (Int) -> IO ()
draw' :: Ptr () -> Int -> Int -> IO ()
draw' a1 :: Ptr ()
a1 a2 :: Int
a2 a3 :: Int
a3 =
  let {a1' = id a1} in 
  let {a2' :: CInt
a2' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a2} in 
  let {a3' :: CInt
a3' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a3} in 
  Ptr () -> CInt -> CInt -> IO ()
draw''_ Ptr ()
a1' CInt
a2' CInt
a3' IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
  () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{-# LINE 122 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ (Position ->  IO ())) => Op (Draw ()) RGBImage 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 ()

{-# LINE 125 "src/Graphics/UI/FLTK/LowLevel/RGBImage.chs" #-}

instance (impl ~ ( IO ())) => Op (Uncache ()) RGBImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> uncache' imagePtr

-- $hierarchy
-- @
-- "Graphics.UI.FLTK.LowLevel.Image"
--  |
--  v
-- "Graphics.UI.FLTK.LowLevel.RGBImage"
-- @

-- $functions
-- @
-- colorAverage :: 'Ref' 'RGBImage' -> 'Color' -> 'Float' -> 'IO' ()
--
-- copy :: 'Ref' 'RGBImage' -> 'Maybe' 'Size' -> 'IO' ('Maybe' ('Ref' orig))
--
-- desaturate :: 'Ref' 'RGBImage' -> 'IO' ()
--
-- destroy :: 'Ref' 'RGBImage' -> 'IO' ()
--
-- draw :: 'Ref' 'RGBImage' -> 'Position' -> 'IO' ()
--
-- drawResize :: 'Ref' 'RGBImage' -> 'Position' -> 'Size' -> 'Maybe' 'X' -> 'Maybe' 'Y' -> 'IO' ()
--
-- getCount :: 'Ref' 'RGBImage' -> 'IO' ('Int')
--
-- getD :: 'Ref' 'RGBImage' -> 'IO' ('Int')
--
-- getH :: 'Ref' 'RGBImage' -> 'IO' ('Int')
--
-- getLd :: 'Ref' 'RGBImage' -> 'IO' ('Int')
--
-- getW :: 'Ref' 'RGBImage' -> 'IO' ('Int')
--
-- inactive :: 'Ref' 'RGBImage' -> 'IO' ()
--
-- uncache :: 'Ref' 'RGBImage' -> 'IO' ()
-- @

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_New"
  rgbImageNew''_ :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_New_With_D"
  rgbImageNew_WithD''_ :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_New_With_LD"
  rgbImageNew_WithLD''_ :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_New_With_D_LD"
  rgbImageNew_WithD_LD''_ :: ((C2HSImp.Ptr C2HSImp.CUChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_Destroy"
  flImageDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_w"
  w''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_h"
  h''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_d"
  d''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_ld"
  ld''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_count"
  count''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_copy_with_w_h"
  copyWithWH''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_copy"
  copy''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_color_average"
  colorAverage''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_inactive"
  inactive''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_desaturate"
  desaturate''_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_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/RGBImage.chs.h Fl_RGB_Image_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/RGBImage.chs.h Fl_RGB_Image_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/RGBImage.chs.h Fl_RGB_Image_draw_with"
  drawWith''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_draw"
  draw''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/RGBImage.chs.h Fl_RGB_Image_uncache"
  uncache''_ :: ((C2HSImp.Ptr ()) -> (IO ()))